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

ber: Create a simple DER Stream and test re-encoding

This commit is contained in:
Holger Hans Peter Freyther 2011-03-30 14:43:51 +02:00
parent ac7437d3d4
commit 4d5a287b1b
3 changed files with 49 additions and 0 deletions

View File

@ -283,3 +283,29 @@ of X.690 and provide very basic reading of a stream.'>
^ ret
]
]
BERTLVStream subclass: DERTLVStream [
<comment: 'I am DER Stream. I can produce valid DER streams
from a tupled input.'>
nextPut: aTuple [
aTuple first writeOn: base.
aTuple first isConstructed
ifTrue: [
| stream der |
stream := WriteStream on: (base species new: 1).
(self class on: stream) nextPutAll: aTuple second.
BERLength writeLength: stream contents size on: base.
base nextPutAll: stream contents.
]
ifFalse: [
BERLength writeLength: aTuple second size on: base.
base nextPutAll: aTuple second.
].
]
nextPutAll: aTupleList [
aTupleList do: [:each | self nextPut: each].
]
]

View File

@ -112,3 +112,25 @@ TestCase subclass: BERTLVStreamTest [
self assert: value second size = 3.
]
]
TestCase subclass: DERTLVStreamTest [
<comment: 'I test DER encoding to some degree'>
testDecodeEncodeAll [
| data decoded stream |
"I test that we can encode what we decode. At least to
some very very basic degree."
data := #(16rA1 16r13 16r02 16r01 16r04 16r02 16r01 16r3B
16r30 16r0B 16r04 16r01 16r0F 16r04 16r06 16r2A
16rD5 16r4C 16r16 16r1B 16r01) asByteArray.
decoded := (DERTLVStream on: data readStream) nextAllRecursive.
stream := WriteStream on: (ByteArray new: 20).
(DERTLVStream on: stream) nextPutAll: decoded.
self assert: data ~= decoded.
self assert: stream contents = data.
]
]

View File

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