smalltalk
/
osmo-st-asn1
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-asn1/BERTLVStreamTest.st

137 lines
4.4 KiB
Smalltalk
Raw Normal View History

"
(C) 2011 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
TestCase subclass: BERTagTest [
testSimpleTag [
<category: 'test'>
self assert: (BERTag parseFrom: #(16rA1) asByteArray readStream) asTuple = #(2 true 1).
]
testFromTuple [
| tuple |
<category: 'test'>
tuple := #(2 true 1).
self assert: (BERTag fromTuple: tuple) asTuple = tuple.
]
testWriteTuple [
| tuple stream |
<category: 'test'>
tuple := #(2 true 1).
stream := WriteStream on: (ByteArray new: 1).
(BERTag fromTuple: tuple) writeOn: stream.
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.
]
]
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.
self assert: value first asTuple = #(2 true 1).
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.
]
]