aboutsummaryrefslogtreecommitdiffstats
path: root/BERTLVStreamTest.st
blob: 113672d499226eae167b31c9cbf19040725071f7 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
"
 (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.
    ]
]