diff --git a/IPAConstants.st b/IPAConstants.st index add1fce..ed52050 100644 --- a/IPAConstants.st +++ b/IPAConstants.st @@ -22,6 +22,7 @@ Object subclass: IPAConstants [ IPAConstants class >> protocolSCCP [ ^ 16rFD ] IPAConstants class >> protocolIPA [ ^ 16rFE ] IPAConstants class >> protocolOML [ ^ 16rFF ] + IPAConstants class >> protocolOSMO [ ^ 16rEE ] IPAConstants class >> msgPing [ ^ 16r00 ] IPAConstants class >> msgPong [ ^ 16r01 ] @@ -39,6 +40,11 @@ Object subclass: IPAConstants [ IPAConstants class >> idtagIpaddr [ ^ 16r06 ] IPAConstants class >> idtagMacaddr [ ^ 16r07 ] IPAConstants class >> idtagUnit [ ^ 16r08 ] + + "Extensions in Osmocom coming with the OsmoExtension header" + IPAConstants class >> osmoCtrl [ ^ 16r00 ] + IPAConstants class >> osmoMgcp [ ^ 16r01 ] + IPAConstants class >> osmoLac [ ^ 16r02 ] ] CPackedStruct subclass: IPASCCPState [ diff --git a/IPADispatcher.st b/IPADispatcher.st index fae317c..b8edcd0 100644 --- a/IPADispatcher.st +++ b/IPADispatcher.st @@ -1,5 +1,5 @@ " - (C) 2010 by Holger Hans Peter Freyther + (C) 2010-2011 by Holger Hans Peter Freyther All Rights Reserved This program is free software: you can redistribute it and/or modify diff --git a/ISUP.st b/ISUP.st index 5c9d357..49fdbc5 100644 --- a/ISUP.st +++ b/ISUP.st @@ -182,6 +182,28 @@ Object subclass: ISUPConstants [ MSGStructure subclass: ISUPMessage [ + ISUPMessage class >> decodeByteStream: aStream [ + + | col cic type | + cic := (aStream next: 2) shortAt: 1. + type := (aStream next: 1) at: 1. + col := self decodeByteStream: aStream type: type. + + ^ OrderedCollection with: cic with: type with: col. + ] + + ISUPMessage class >> encodeCollection: aCollection [ + | msg type | + msg := Osmo.MessageBuffer new. + type := aCollection at: 2. + + msg put16: (aCollection at: 1). + msg putByte: type. + + msg putByteArray: (self encodeCollection: (aCollection at: 3) type: type). + ^ msg + ] + parseVariable: aStream with: aClass into: decoded [ | pos ptr res | pos := aStream position. @@ -203,5 +225,10 @@ MSGStructure subclass: ISUPMessage [ ptr := aStream next. aStream skip: ptr - 1. ] + + prepareWrite: aStream [ + | len | + len := self variable size. + ] ] diff --git a/ISUPTests.st b/ISUPTests.st index 4e5b1e5..ea02578 100644 --- a/ISUPTests.st +++ b/ISUPTests.st @@ -49,6 +49,22 @@ TestCase subclass: ISUPGeneratedTest [ ]. ] + testDecode [ + | decode struct data | + decode := #(16r15 16r00 16r01 16r00 16r00 16r00 16r0A 16r00 + 16r02 16r0B 16r09 16r04 16r10 16r00 16r19 16r79 + 16r64 16r64 16r64 16r78 16r0A 16r09 16r02 16r13 + 16r00 16r79 16r51 16r20 16r01 16r79 16r42 16r00) asByteArray. + + struct := ISUPMessage decodeByteStream: decode readStream. + struct inspect. + + data := ISUPMessage encodeCollection: struct. + decode printNl. + data asByteArray printNl. + self assert: data asByteArray = decode. + ] + testClassCount [ self assert: ISUPMessage allSubclasses size = 46. ] diff --git a/MessageBuffer.st b/MessageBuffer.st index 6b15a4b..d8fa476 100644 --- a/MessageBuffer.st +++ b/MessageBuffer.st @@ -46,6 +46,14 @@ Collection subclass: MessageBuffer [ chunks add: aByteArray. ] + put16: aInt [ + | data low high | + low := (aInt bitAnd: 16rFF). + high := (aInt bitShift: -8) bitAnd: 16rFF. + data := ByteArray with: low with: high. + chunks add: data. + ] + putLen16: aInt [ | data low high | low := (aInt bitShift: -8) bitAnd: 16rFF. diff --git a/MessageStructure.st b/MessageStructure.st index 231610a..ba494c4 100644 --- a/MessageStructure.st +++ b/MessageStructure.st @@ -16,6 +16,13 @@ along with this program. If not, see . " +Object extend [ + subclassResponsibility [ + thisContext backtrace printNl. + SystemExceptions.SubclassResponsibility signal + ] +] + " The next attempt to generalize the message pattern. We will just describe messages that have a type, mandantory and optional parameters. The parameters @@ -52,6 +59,15 @@ Object subclass: MSGStructure [ ^ structure decodeByteStream: aStream. ] + MSGStructure class >> encodeCollection: aCollection type: aType [ + | structure | + "This is a generic encoding method that will put the collection + onto a MessageBuffer class." + + structure := self findStructure: aType. + ^ structure encodeCollection: aCollection. + ] + type: aType [ type := aType. @@ -192,12 +208,65 @@ Object subclass: MSGStructure [ ]. ]. - aStream atEnd ifFalse: [ - decoded inspect. - ^ self error: 'Stream should be at the end. Unconsumed bytes.'. + "TODO: complain about unfetched bytes?" + ^ decoded + ] + + writeFixed: msg with: clazz from: field [ + + + (field isKindOf: clazz) ifFalse: [ + ^ self error: 'Mandantory information must be %1 but was %2.' % {clazz. field.}. ]. - ^ decoded + msg nextPutAll: field data. + ] + + writeVariable: msg with: clazz from: field [ + + + (field isKindOf: clazz) ifFalse: [ + ^ self error: 'Variable information must be %1 but was %2.' % {clazz. field.} + ]. + + "TODO: Respect the lengthLength here" + msg nextPut: field data size. + msg nextPutAll: field data. + ] + + prepareWrite: aStream [ + ] + + encodeCollection: aCollection [ + | stream msg fixed_done | + + + msg := WriteStream on: (ByteArray new: 3). + stream := aCollection readStream. + fixed_done := false. + + self fieldsDo: [:type :clazz | + type = #fixed ifTrue: [ + self writeFixed: msg with: clazz from: stream next.] + ifFalse: [ + fixed_done ifFalse: [ + fixed_done := true. + self prepareWrite: msg. + ]. + ]. + + type = #variable ifTrue: [ + self writeVariable: msg with: clazz from: stream next. + ]. +" + type = #optional ifTrue: [ + ]. + type = #optionals ifTrue: [ + ]. +" + ]. + + ^ msg contents ] ]