smalltalk
/
osmo-st-asn1
Archived
1
0
Fork 0

ber: Test the encoding/decoding of the Length on a BER string

This commit is contained in:
Holger Hans Peter Freyther 2011-03-30 10:10:29 +02:00
parent b176bea4b5
commit 4d0b83c099
3 changed files with 76 additions and 0 deletions

View File

@ -178,3 +178,44 @@ Object subclass: BERTag [
^ Array with: self classType with: self isConstructed with: self tagValue.
]
]
Object subclass: BERLength [
<category: 'osmo-asn1'>
<comment: 'I can handle the length for definite and indefinite length. I wonder
of myself if I should be class or instance based or even be a SmallInteger or an
extension to a SmallInteger. Should I have a method called isIndefinite. Time will tell.'>
BERLength class >> new [
^ self error: 'Only use the class helper functions'
]
BERLength class >> parseMultiOctet: len from: aStream [
"I should handle paragraph 8.1.3.5. But I don't."
<category: 'private-decoding'>
^ self error: 'Decoding multi octet length is not implemented'.
]
BERLength class >> parseFrom: aStream [
| len |
<category: 'decoding'>
len := aStream next.
^ (len bitAnd: 16r80) > 0
ifTrue: [self parseMultiOctet: len from: aStream]
ifFalse: [len].
]
BERLength class >> writeMultiOctet: aLength on: aStream [
<category: 'private-encoding'>
^ self error: 'Multi octet writing is not implemented yet'.
]
BERLength class >> writeLength: aLength on: aStream [
<category: 'encoding'>
^ aLength > 16r7F
ifTrue: [self writeMultiOctet: aLength on: aStream]
ifFalse: [aStream nextPut: aLength].
]
]

View File

@ -41,3 +41,37 @@ TestCase subclass: BERTagTest [
self assert: stream contents = #(16rA1) asByteArray
]
]
TestCase subclass: BERLengthTest [
testSimpleLengthRead [
| read |
read := BERLength parseFrom: #(10) asByteArray readStream.
self assert: read = 10.
]
testSimpleLenghWrite [
| write stream |
stream := WriteStream on: (ByteArray new: 1).
write := BERLength writeLength: 10 on: stream.
self assert: stream contents = #(10) asByteArray
]
testIndefiniteRead [
"I test that indefinite coding is not implemented"
self should: [BERLength parseFrom: #(16r80) asByteArray readStream] raise: Error
]
testLongRead [
"I test that a multi octet length can not be read"
self should: [BERLength parseFrom: #(16r83 0 0 0) asByteArray readStream] raise: Error
]
testLongWrite [
| stream |
"I test that a multi octet length can not be written"
stream := WriteStream on: (ByteArray new: 1).
self should: [BERLength writeLength: 128 on: stream] raise: Error.
]
]

View File

@ -9,6 +9,7 @@
<sunit>Osmo.BERTest</sunit>
<sunit>Osmo.BERTagTest</sunit>
<sunit>Osmo.BERTLVStreamTest</sunit>
<sunit>Osmo.BERLengthTest</sunit>
<filein>Tests.st</filein>
<filein>BERTLVStreamTest.st</filein>
</test>