diff --git a/BERTLVStream.st b/BERTLVStream.st index 3aff0ef..fdcb584 100644 --- a/BERTLVStream.st +++ b/BERTLVStream.st @@ -178,3 +178,44 @@ Object subclass: BERTag [ ^ Array with: self classType with: self isConstructed with: self tagValue. ] ] + +Object subclass: BERLength [ + + + + 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." + + ^ self error: 'Decoding multi octet length is not implemented'. + ] + + BERLength class >> parseFrom: aStream [ + | len | + + + len := aStream next. + ^ (len bitAnd: 16r80) > 0 + ifTrue: [self parseMultiOctet: len from: aStream] + ifFalse: [len]. + ] + + BERLength class >> writeMultiOctet: aLength on: aStream [ + + ^ self error: 'Multi octet writing is not implemented yet'. + ] + + BERLength class >> writeLength: aLength on: aStream [ + + + ^ aLength > 16r7F + ifTrue: [self writeMultiOctet: aLength on: aStream] + ifFalse: [aStream nextPut: aLength]. + ] +] + diff --git a/BERTLVStreamTest.st b/BERTLVStreamTest.st index a274d8d..41bc642 100644 --- a/BERTLVStreamTest.st +++ b/BERTLVStreamTest.st @@ -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. + ] +] + diff --git a/package.xml b/package.xml index f22cbf3..52dfad9 100644 --- a/package.xml +++ b/package.xml @@ -9,6 +9,7 @@ Osmo.BERTest Osmo.BERTagTest Osmo.BERTLVStreamTest + Osmo.BERLengthTest Tests.st BERTLVStreamTest.st