diff --git a/osmo-st-asn1/BERTLVStream.st b/osmo-st-asn1/BERTLVStream.st new file mode 100644 index 0000000..5c57a9e --- /dev/null +++ b/osmo-st-asn1/BERTLVStream.st @@ -0,0 +1,319 @@ +" + (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 . +" + +Object subclass: BERTag [ + | classType tagValue constructed | + + + + BERTag class >> classUniversal [ + + ^ 0 + ] + + BERTag class >> classApplication [ + + ^ 1 + ] + + BERTag class >> classContext [ + + ^ 2 + ] + + BERTag class >> classPrivate [ + + ^ 3 + ] + + BERTag class >> new [ + + ^ super new initialize + ] + + BERTag class >> parseFrom: aStream [ + + ^ self new + parseFrom: aStream; + yourself + ] + + BERTag class >> fromTuple: aTuple [ + + ^ self new + fromTuple: aTuple; + yourself + ] + + BERTag class >> endOfContents [ + + ^ self fromTuple: #(0 false 0) + ] + + BERTag class >> boolean [ + + ^ self fromTuple: #(0 false 1) + ] + + BERTag class >> integer [ + + ^ self fromTuple: #(0 false 2) + ] + + BERTag class >> octetString [ + + ^ self fromTuple: #(0 false 4) + ] + + BERTag class >> null [ + + ^ self fromTuple: #(0 false 5) + ] + + BERTag class >> enumerated [ + + ^ self fromTuple: #(0 false 10) + ] + + BERTag class >> sequence [ + + ^ self fromTuple: #(0 true 16) + ] + + BERTag class >> set [ + + ^ self fromTuple: #(0 true 17) + ] + + initialize [ + + classType := BERTag classUniversal. + tagValue := 0. + constructed := false. + ] + + = aOther [ + + + (aOther isKindOf: self class) ifTrue: [^self asTuple = aOther asTuple]. + ^ self asTuple = aOther. + ] + + parseExtendedTag: aStream [ + + + ^ self error: 'Extended tags are not implemented yet'. + ] + + parseFrom: aStream [ + | tmp | + + + tmp := aStream next. + classType := (tmp bitAnd: 16rC0) bitShift: -6. + constructed := (tmp bitAnd: 16r20) > 0. + tagValue := tmp bitAnd: 16r1F. + + "This is an extended tag" + (tagValue = 16r1F) ifTrue: [ + self parseExtendedTag: aStream. + ]. + ] + + fromTuple: aTuple [ + + + classType := aTuple first bitAnd: 16r3. + constructed := aTuple second. + tagValue := aTuple third. + ] + + writeExtendedTag: aStream [ + + self error: 'Cannot encode extended tag.' + ] + + writeOn: aStream [ + + tagValue >= 16r1F + ifTrue: [self writeExtendedTag: aStream.] + ifFalse: [| tag | + tag := classType bitShift: 6. + self isConstructed ifTrue: [tag := tag bitOr: 16r20]. + tag := tag bitOr: self tagValue. + aStream nextPut: tag. + ]. + ] + + classType [ + + ^ classType + ] + + isConstructed [ + + ^ constructed + ] + + isPrimitive [ + + ^ self isConstructed not + ] + + tagValue [ + + ^ tagValue + ] + + asTuple [ + + ^ Array with: self classType with: self isConstructed with: self tagValue. + ] + + printOn: aStream [ + + ^ aStream nextPutAll: '%1 %2' % {self class. self asTuple.} + ] +] + +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]. + ] +] + +Object subclass: BERTLVStream [ + | base | + + + + BERTLVStream class >> on: aStream [ + + ^ self new + stream: aStream; + yourself + ] + + stream: aStream [ + + base := aStream. + ] + + atEnd [ + + ^ base atEnd + ] + + next [ + | tag len dat | + + + 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 + ] +] + +BERTLVStream subclass: DERTLVStream [ + + + + 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]. + ] +] diff --git a/osmo-st-asn1/BERTLVStreamTest.st b/osmo-st-asn1/BERTLVStreamTest.st new file mode 100644 index 0000000..17e124b --- /dev/null +++ b/osmo-st-asn1/BERTLVStreamTest.st @@ -0,0 +1,191 @@ +" + (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 . +" + +TestCase subclass: BERTagTest [ + + + testSimpleTag [ + + self assert: (BERTag parseFrom: #(16rA1) asByteArray readStream) asTuple = #(2 true 1). + ] + + testFromTuple [ + | tuple | + + + tuple := #(2 true 1). + self assert: (BERTag fromTuple: tuple) asTuple = tuple. + ] + + testWriteTuple [ + | tuple stream | + + + 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. + ] + + testMoreGSM [ + | data | + data := #(16rA1 16r20 16r02 16r01 16r01 16r02 16r01 16r3B + 16r30 16r18 16r04 16r01 16r0F 16r04 16r13 16r2A + 16rD5 16r4C 16r26 16r53 16rC5 16r64 16rB1 16r18 + 16r2D 16r16 16rAB 16rC9 16r68 16rB1 16rD8 16r0D + 16r37 16r02) asByteArray. + (BERTLVStream on: data readStream) nextAllRecursive. + ] +] + +TestCase subclass: DERTLVStreamTest [ + + + + 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. + ] + + testUSSDUnstructReqEncode [ + | req str wanted | + wanted := #(16rA1 16r13 16r02 16r01 16r04 16r02 16r01 16r3B 16r30 16r0B 16r04 16r01 16r0F 16r04 16r06 16r2A 16rD5 16r4C 16r16 16r1B 16r01) asByteArray. + + req := {BERTag fromTuple: #(2 true 1). OrderedCollection + with: {BERTag integer. #(4).} + with: {BERTag integer. #(59).} + with: {BERTag fromTuple: #(0 true 16). OrderedCollection + with: {BERTag octetString. #(15).} + with: {BERTag octetString. #(16r2A 16rD5 16r4C 16r16 16r1B 16r01)}.}.}. + + str := WriteStream on: (ByteArray new: 20). + (DERTLVStream on: str) nextPut: req. + + self assert: str contents = wanted. + ] + + testUSSDReturnResult [ + | req str wanted | + + wanted := #(16rA2 16r38 16r02 16r01 16r04 16r30 16r33 16r02 16r01 16r3B 16r30 16r2E 16r04 16r01 16r0F 16r04 16r29 16rC2 16r30 16r3B 16rEC 16r1E 16r97 16r41 16rE9 16rB9 16r4E 16r46 16r8B 16rB9 16r60 16r30 16r50 16rDD 16r9D 16rA6 16rCF 16r59 16r65 16r3C 16r3C 16r2D 16r4F 16rBB 16rCF 16rA0 16rB7 16r5B 16r17 16r8B 16rB5 16r60 16rB7 16r96 16r0C 16r16 16r8B 16r01) asByteArray. + + req := {BERTag fromTuple: #(2 true 2). OrderedCollection + with: {BERTag integer. #(4)} + with: {BERTag sequence. OrderedCollection + with: {BERTag integer. #(59)} + with: {BERTag sequence. OrderedCollection + with: {BERTag octetString. #(15)} + with: {BERTag octetString. #(194 48 59 236 30 151 65 233 185 78 70 139 185 96 48 80 221 157 166 207 89 101 60 60 45 79 187 207 160 183 91 23 139 181 96 183 150 12 22 139 1)} + } + } + }. + + str := WriteStream on: (ByteArray new: 2). + (DERTLVStream on: str) nextPut: req. + self assert: str contents = wanted. + ] +] diff --git a/osmo-st-asn1/README b/osmo-st-asn1/README new file mode 100644 index 0000000..62e00bd --- /dev/null +++ b/osmo-st-asn1/README @@ -0,0 +1 @@ +ASN1 Code to work on TCAP/MAP/Camel... diff --git a/osmo-st-asn1/package.xml b/osmo-st-asn1/package.xml new file mode 100644 index 0000000..c762018 --- /dev/null +++ b/osmo-st-asn1/package.xml @@ -0,0 +1,14 @@ + + OsmoASN1 + Osmo + + BERTLVStream.st + + + Osmo.BERTagTest + Osmo.BERTLVStreamTest + Osmo.BERLengthTest + Osmo.DERTLVStreamTest + BERTLVStreamTest.st + +