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

ber: Provide a simple BERTLVStream class

The BERTLVStream is able to read BER tuples from a stream, it
can also read all tuples and it can recursively read tuples into
an OrderedCollection.
This commit is contained in:
Holger Hans Peter Freyther 2011-03-30 14:09:43 +02:00
parent bb2cea8520
commit 675abe4fb4
2 changed files with 97 additions and 0 deletions

View File

@ -224,3 +224,62 @@ extension to a SmallInteger. Should I have a method called isIndefinite. Time wi
]
]
Object subclass: BERTLVStream [
| base |
<category: 'osmo-asn1'>
<comment: 'I am a Tag Value Length (TLV) Stream for Basic Encoding Rules (BER)
of X.690 and provide very basic reading of a stream.'>
BERTLVStream class >> on: aStream [
<category: 'creation'>
^ self new
stream: aStream;
yourself
]
stream: aStream [
<category: 'init'>
base := aStream.
]
atEnd [
<category: 'decoding'>
^ base atEnd
]
next [
| tag len dat |
<category: 'decoding'>
tag := BERTag parseFrom: base.
len := BERLength parseFrom: base.
dat := base next: len.
^ Array with: tag with: dat.
]
nextAll [
| ret |
ret := OrderedCollection new.
[self atEnd] whileFalse: [ret add: self next].
^ ret
]
nextAllRecursive [
| ret |
ret := OrderedCollection new.
[self atEnd] whileFalse: [| dat |
dat := self next.
dat first isConstructed
ifTrue: [|other|
other := (self class on: dat second readStream) nextAllRecursive.
ret add: (Array with: dat first with: other)]
ifFalse: [ret add: dat].
].
^ ret
]
]

View File

@ -75,3 +75,41 @@ TestCase subclass: BERLengthTest [
]
]
TestCase subclass: BERTLVStreamTest [
testParseLength [
| data stream value |
"I parse a simple example."
data := #(16r03 16r07 16r04 16r0A 16r3B 16r5F 16r29 16r1C 16rD0) asByteArray.
stream := BERTLVStream on: data readStream.
value := stream next.
self assert: value first asTuple = #(0 false 3).
self assert: value second = #(16r04 16r0A 16r3B 16r5F 16r29 16r1C 16rD0) asByteArray.
]
testParseSequence [
| data stream value inner |
data := #(16r30 16r0A
16r16 16r05 83 109 105 116 104
16r01 16r01 16rFF) asByteArray.
stream := BERTLVStream on: data readStream.
value := stream next.
self assert: value first asTuple = #(0 true 16r10).
self assert: value second = #(16r16 16r05 83 109 105 116 104 16r01 16r01 16rFF) asByteArray
]
testSimpleGSM [
| data stream value |
"I should parse a simple GSM payload but the test is too basic. We
don't carefully compare the result."
data := #(16rA1 16r13 16r02 16r01 16r04 16r02 16r01 16r3B
16r30 16r0B 16r04 16r01 16r0F 16r04 16r06 16r2A
16rD5 16r4C 16r16 16r1B 16r01) asByteArray.
value := (BERTLVStream on: data readStream) nextAllRecursive first.
value second size printNl.
self assert: value first asTuple = #(2 true 1).
self assert: value second size = 3.
]
]