diff --git a/osmo-st-network/.gitignore b/osmo-st-network/.gitignore new file mode 100644 index 0000000..45d62d8 --- /dev/null +++ b/osmo-st-network/.gitignore @@ -0,0 +1 @@ +*.sw? diff --git a/osmo-st-network/Makefile b/osmo-st-network/Makefile new file mode 100644 index 0000000..986159d --- /dev/null +++ b/osmo-st-network/Makefile @@ -0,0 +1,75 @@ + +GST_PACKAGE = gst-package +GST_CONVERT = gst-convert + +CONVERT_RULES = -r'Osmo.LogManager->LogManager' \ + -r'Osmo.LogArea->LogArea' \ + -r'Osmo.LogLevel->LogLevel' \ + -r'Osmo.TimerScheduler->TimerScheduler' \ + -r'Sockets.StreamSocket->SocketStream' \ + -r'DateTime->DateAndTime' \ + -r'(Duration milliseconds: ``@args1) -> (Duration milliSeconds: ``@args1)' \ + -r'PP.PPCompositeParser->PPCompositeParser' \ + -r'PP.PPCompositeParserTest->PPCompositeParserTest' \ + -r'STInST.RBProgramNodeVisitor->RBProgramNodeVisitor' \ + -r'STInST.RBBracketedMethodParser->RBParser' \ + -r'Osmo.MessageBuffer->MessageBuffer' \ + -r'SystemExceptions.NotFound->NotFound' \ + -r'(``@object substrings: ``@args1)->(``@object subStrings: ``@args1)' \ + -r'(Dictionary from: ``@args1)->(Dictionary newFrom: ``@args1)' \ + -r'(``@object copyFrom: ``@args1)->(``@object copyFrom: ``@args1 to: ``@object size)' \ + -r'(``@object nl)->(``@object cr; lf)' \ + -r'(``@object methodSourceString)->(``@object sourceCode)' \ + -C -IPAGSTTests + +# Can not be parsed right now.. +# -r'(``@object => ``@args1)->(``@object ==> ``@args1)' + +CORE = \ + core/Extensions.st core/MessageStructure.st core/MessageBuffer.st \ + core/LogAreas.st core/TLV.st core/TLVTests.st + +IPA = \ + ipa/IPAConstants.st ipa/IPADispatcher.st ipa/IPAMuxer.st \ + ipa/IPAProtoHandler.st ipa/IPAMsg.st \ + +SCCP = \ + sccp/SCCP.st sccp/SCCPAddress.st \ + sccp/SCCPGlobalTitle.st sccp/SCCPGlobalTitleTranslation.st + +ISUP = \ + isup/ISUP.st isup/isup_generated.st isup/ISUPExtensions.st \ + isup/ISUPTests.st + +UA = \ + ua/XUA.st + +M2UA = \ + m2ua/M2UAConstants.st m2ua/M2UAMSG.st m2ua/M2UATag.st m2ua/M2UAMessages.st \ + m2ua/M2UAStates.st m2ua/M2UAAspStateMachine.st \ + m2ua/M2UAApplicationServerProcess.st m2ua/M2UALayerManagement.st \ + m2ua/M2UAExamples.st m2ua/M2UATerminology.st m2ua/M2UATests.st + + +OSMO = \ + osmo/LogAreaOsmo.st \ + osmo/OsmoUDPSocket.st osmo/OsmoCtrlLogging.st \ + osmo/OsmoStreamSocketBase.st \ + osmo/OsmoCtrlGrammar.st osmo/OsmoAppConnection.st \ + osmo/OsmoCtrlConnection.st osmo/OsmoCtrlGrammarTest.st + +MTP3 = \ + mtp3/MTP3Messages.st mtp3/MTP3MessagesTests.st + + + +all: + $(GST_PACKAGE) --test package.xml + +convert: + $(GST_CONVERT) $(CONVERT_RULES) -F squeak -f gst \ + -o fileout.st pharo-porting/compat_for_pharo.st \ + $(CORE) $(IPA) $(SCCP) $(ISUP) $(UA) $(OSMO) $(MTP3) $(M2UA) \ + Tests.st pharo-porting/changes_for_pharo.st + sed -i s,"=>","==>",g fileout.st + diff --git a/osmo-st-network/README b/osmo-st-network/README new file mode 100644 index 0000000..5fcf681 --- /dev/null +++ b/osmo-st-network/README @@ -0,0 +1 @@ +osmo-network a module for networking (SCCP, M3UA, IPA) protocol handling diff --git a/osmo-st-network/Tests.st b/osmo-st-network/Tests.st new file mode 100644 index 0000000..e395745 --- /dev/null +++ b/osmo-st-network/Tests.st @@ -0,0 +1,397 @@ +" + (C) 2010-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 . +" +"Test Case for Osmo-Network" + +TestCase subclass: SCCPTests [ + + + SCCPTests class >> packageNamesUnderTest [ + + ^ #('OsmoNetwork') + ] + + testCreateForSSN [ + | addr | + addr := SCCPAddress createForSSN: 'hlr'. + self assert: addr subSystemNumber = SCCPAddress ssnHLR. + self assert: addr routedOnSSN. + self assert: addr globalTitle isNil. + self assert: addr pointCode isNil. + ] + + testPNCCreate [ + | pnc | + + pnc := SCCPPNC new. + pnc at: SCCPHelper pncData put: #(1 2 3) asByteArray. + self assert: pnc toMessage asByteArray = #(15 3 1 2 3 0) asByteArray. + ] + + testReleasedFormat [ + | rlsd msg | + rlsd := SCCPConnectionReleased initWithDst: 16r401 src: 16r1F0A01 cause: 16rFE. + msg := rlsd toMessage asByteArray. + + self assert: msg = #(4 1 4 0 1 16r0A 16r1F 16rFE 1 0) asByteArray + ] + + testDT1 [ + | dt1 msg target | + target := #(6 1 4 0 0 1 4 49 50 51 52) asByteArray. + dt1 := SCCPConnectionData initWith: 16r401 data: '1234' asByteArray. + msg := dt1 toMessage asByteArray. + + self assert: msg = target. + + dt1 := SCCPMessage decode: target. + self assert: dt1 dst = 16r401. + self assert: dt1 data = '1234' asByteArray. + self assert: dt1 toMessage asByteArray = target. + ] + + testCR [ + | cr msg target | + target := #(1 191 0 3 2 2 4 2 66 254 15 4 49 50 51 52 0) asByteArray. + + "encode it" + cr := SCCPConnectionRequest + initWith: 16r0300BF + dest: (SCCPAddress createWith: 254) + data: '1234' asByteArray. + msg := cr toMessage asByteArray. + + self assert: msg = target. + + "now decode it" + cr := SCCPMessage decode: target. + self assert: (cr isKindOf: SCCPConnectionRequest). + self assert: cr src = 16r0300BF. + self assert: cr dest asByteArray = (SCCPAddress createWith: 254) asByteArray. + self assert: cr data = '1234' asByteArray. + + "now encode it again" + self assert: cr toMessage asByteArray = target. + ] + + testCC [ + | target cc | + + target := #(2 191 0 3 1 3 176 2 1 0) asByteArray. + + cc := SCCPConnectionConfirm + initWithSrc: 16rB00301 dst: 16r0300BF. + self assert: cc toMessage asByteArray = target. + + cc := SCCPMessage decode: target. + self assert: (cc isKindOf: SCCPConnectionConfirm). + self assert: cc dst = 16r0300BF. + self assert: cc src = 16rB00301. + + self assert: cc toMessage asByteArray = target. + ] + + testRlsd [ + | target rlsd | + + target := #(4 154 2 0 66 5 5 0 1 0 ) asByteArray. + rlsd := SCCPConnectionReleased + initWithDst: 16r0029A src: 16r50542 + cause: 0. + self assert: rlsd toMessage asByteArray = target. + + rlsd := SCCPMessage decode: target. + self assert: rlsd dst = 16r0029A. + self assert: rlsd src = 16r50542. + self assert: rlsd cause = 0. + self assert: rlsd toMessage asByteArray = target. + ] + + testCreateRLSD [ + | target rlsd | + target := #(4 154 2 0 66 5 5 0 1 0 ) asByteArray. + rlsd := SCCPHelper createRLSD: 16r50542 dest: 16r0029A cause: 0. + self assert: rlsd asByteArray = target. + ] + + testRlc [ + | target rlc | + + target := #(5 1 8 119 62 4 5 ) asByteArray. + rlc := SCCPConnectionReleaseComplete + initWithDst: 16r770801 src: 16r05043E. + self assert: rlc toMessage asByteArray = target. + + rlc := SCCPMessage decode: target. + self assert: rlc dst = 16r770801. + self assert: rlc src = 16r05043E. + self assert: rlc toMessage asByteArray = target. + ] + + testUdt [ + | target udt called calling | + target := #(9 0 3 7 11 4 67 7 0 254 4 67 92 0 254 3 1 2 3) asByteArray. + called := SCCPAddress createWith: 254 pointCode: 7. + calling := SCCPAddress createWith: 254 pointCode: 92. + udt := SCCPUDT + initWith: called + calling: calling + data: #(1 2 3) asByteArray. + self assert: udt toMessage asByteArray = target. + udt := SCCPMessage decode: target. + self assert: (udt isKindOf: SCCPUDT). + self assert: udt calledAddr ssn = 254. + self assert: udt calledAddr pointCode = 7. + self assert: udt callingAddr ssn = 254. + self assert: udt callingAddr pointCode = 92. + self assert: udt toMessage asByteArray = target + ] + + testUDTClass [ + | target udt | + target := #(9 129 3 13 24 10 18 6 0 18 4 83 132 9 0 55 11 18 7 0 + 18 4 54 25 8 0 4 49 70 100 68 73 4 81 1 3 78 107 42 + 40 40 6 7 0 17 134 5 1 1 1 160 29 97 27 128 2 7 128 + 161 9 6 7 4 0 0 1 0 27 3 162 3 2 1 0 163 5 161 3 2 1 + 0 108 128 162 12 2 1 64 48 7 2 1 67 48 2 128 0 0 0) asByteArray. + + udt := SCCPMessage decode: target. + self assert: udt udtClass = 1. + self assert: udt errorHandling = 8. + self assert: udt toMessage asByteArray = target. + ] + + testIT [ + | target it | + target := #(16 1 3 176 191 0 3 240 36 66 239) asByteArray. + + it := SCCPMessage decode: target. + self assert: it src = 16r0300BF. + self assert: it dst = 16rB00301. + self assert: it credit = 16rEF. + self assert: it seq = #(16r24 16r42) asByteArray. + self assert: it protoClass = 16rF0. + + self assert: it toMessage asByteArray = target. + ] + + testAddrFromByteArray [ + | byte | + byte := #(191 0 3) asByteArray. + self assert: (SCCPAddrReference fromByteArray: byte) = 16r0300BF + ] + + testAddrGTIFromByteArrray [ + | addr parsed gti | + addr := #(16r0A 16r12 16r06 16r0 16r12 16r04 16r53 16r84 16r09 16r00 16r37) asByteArray. + parsed := SCCPAddress parseFrom: addr. + + self assert: parsed ssn = SCCPAddress ssnHLR. + self assert: parsed asByteArray = addr. + + "Now test the GTI parsing" + gti := parsed gtiAsParsed. + self assert: gti translation = 0. + self assert: gti plan = SCCPGlobalTitle npISDN. + self assert: gti nature = SCCPGlobalTitle naiInternationalNumber. + self assert: gti addr = '3548900073'. + parsed gtiFromAddr: gti. + self assert: parsed asByteArray = addr. + + ] + + testAddrGTIOdd [ + | addr parsed gti | + addr := #(16r0B 16r12 16r08 16r00 16r11 16r04 16r64 16r07 16r97 16r36 16r71 16r03) asByteArray. + parsed := SCCPAddress parseFrom: addr. + + self assert: parsed ssn = SCCPAddress ssnMSC. + self assert: parsed asByteArray = addr. + + "GTI encoding.." + gti := parsed gtiAsParsed. + self assert: gti translation = 0. + self assert: gti plan = SCCPGlobalTitle npISDN. + self assert: gti nature = SCCPGlobalTitle naiInternationalNumber. + self assert: gti addr = '46707963173'. + parsed gtiFromAddr: gti. + self assert: parsed asByteArray = addr. + ] +] + +TestCase subclass: MessageBufferTest [ + + + testAdd [ + | msg1 msg2 msg3 msg_master | + msg1 := MessageBuffer new. + msg2 := MessageBuffer new. + msg3 := MessageBuffer new. + + msg1 putByteArray: #(1 2 3) asByteArray. + msg2 putByteArray: #(4 5 6) asByteArray. + msg3 putByteArray: #(7 8 9) asByteArray. + + msg_master := MessageBuffer new. + msg_master putByteArray: msg1. + msg_master putByteArray: msg2. + msg_master putByteArray: msg3. + + self assert: msg_master size = 9. + self assert: msg_master toByteArray = #(1 2 3 4 5 6 7 8 9) asByteArray. + self assert: msg_master asByteArray = #(1 2 3 4 5 6 7 8 9) asByteArray. + ] + + testEmptyByteArray [ + | msg | + msg := MessageBuffer new. + msg putByteArray: ByteArray new. + self assert: msg size = 0. + self assert: msg toByteArray = #() asByteArray. + ] + + testPrependByteArray [ + | msg | + msg := MessageBuffer new. + msg putByteArray: #(3 4 5) asByteArray. + msg prependByteArray: #(1 2) asByteArray. + self assert: msg toByteArray = #(1 2 3 4 5) asByteArray. + + msg := MessageBuffer new. + msg prependByteArray: #(1 2) asByteArray. + msg putByteArray: #(3 4 5) asByteArray. + self assert: msg toByteArray = #(1 2 3 4 5) asByteArray. + + msg := MessageBuffer new. + msg prependByteArray: #(1 2) asByteArray. + self assert: msg toByteArray = #(1 2) asByteArray. + ] + + testIdentity [ + | msg | + msg := MessageBuffer new. + self assert: msg toMessage == msg. + ] +] + +TestCase subclass: M2UAMSGTests [ + + + testUnique [ + "This should have some sanity checks on the enum" + ] + + testParseTag [ + | inp tag | + inp := #(16r00 16r11 16r00 16r08 16rAC 16r10 16r01 16r51) asByteArray. + tag := M2UATag fromStream: inp readStream. + + self assert: tag nr = 16r11. + self assert: tag data = #(16rAC 16r10 16r01 16r51) asByteArray. + ] + + testCreateTag [ + | tag exp | + tag := M2UATag initWith: 16r11 data: (ByteArray new: 3 withAll: 6). + exp := #(16r00 16r11 16r00 16r07 16r06 16r06 16r06 16r00) asByteArray. + self assert: tag toMessage asByteArray = exp. + ] + + testCreateMessage [ + | msg data out res | + res := #(16r01 16r00 16r03 16r01 16r00 16r00 16r00 16r10 + 16r00 16r11 16r00 16r08 16rAC 16r10 16r01 16r51) asByteArray. + data := #(16rAC 16r10 16r01 16r51) asByteArray. + + msg := M2UAMSG fromClass: M2UAConstants clsASPSM type: M2UAConstants aspsmUp. + msg addTag: (M2UATag initWith: 16r11 data: data). + out := msg toMessage asByteArray. + + self assert: out = res. + ] + + testCreatePaddingMessage [ + | msg data out res | + res := #(16r01 16r00 16r03 16r01 16r00 16r00 16r00 16r10 + 16r00 16r11 16r00 16r07 16rAC 16r10 16r01 16r00) asByteArray. + data := #(16rAC 16r10 16r01) asByteArray. + + msg := M2UAMSG fromClass: M2UAConstants clsASPSM type: M2UAConstants aspsmUp. + msg addTag: (M2UATag initWith: 16r11 data: data). + out := msg toMessage asByteArray. + + self assert: out = res. + ] + + testParseMessage [ + | inp msg | + + inp := #(16r01 16r00 16r03 16r01 16r00 16r00 16r00 16r10 + 16r00 16r11 16r00 16r08 16rAC 16r10 16r01 16r51) asByteArray. + msg := M2UAMSG parseFrom: inp. + self assert: msg msgClass = UAConstants clsASPSM. + self assert: msg msgType = UAConstants aspsmUp. + + inp := #(16r01 16r00 16r06 16r01 16r00 16r00 16r00 16r2C + 16r00 16r01 16r00 16r08 16r00 16r00 16r00 16r00 + 16r03 16r00 16r00 16r1A 16r81 16r5C 16r00 16r07 + 16r00 16r11 16rF0 16rAA 16rAA 16rAA 16rAA 16rAA + 16rAA 16rAA 16rAA 16rAA 16rAA 16rAA 16rAA 16rAA + 16rAA 16rAA 16r00 16r00) asByteArray. + msg := M2UAMSG parseFrom: inp. + self assert: msg msgClass = UAConstants clsMAUP. + self assert: msg msgType = UAConstants maupData. + ] + + testFindTag [ + | inp msg tag | + inp := #(16r01 16r00 16r03 16r01 16r00 16r00 16r00 16r10 16r00 + 16r11 16r00 16r08 16rAC 16r10 16r01 16r51) asByteArray. + msg := M2UAMSG parseFrom: inp. + tag := msg findTag: M2UAConstants tagReserved ifAbsent: [ nil ]. + self assert: tag isNil. + + tag := msg findTag: M2UAConstants tagAspIdent ifAbsent: [self fail]. + self deny: tag isNil. + ] +] + +TestCase subclass: OsmoUDPSocketTest [ + + + createSocket [ + ^ Sockets.DatagramSocket new. + ] + + testSocketCreation [ + | socket rx tx | + socket := OsmoUDPSocket new + name: 'Test Socket'; + start: self createSocket; + yourself. + + "Verify that we are in processing" + rx := socket instVarNamed: #rx. + tx := socket instVarNamed: #tx. + self deny: rx isTerminated. + self deny: tx isTerminated. + + socket stop. + self assert: rx isTerminated. + self assert: tx isTerminated. + ] +] diff --git a/osmo-st-network/contrib/Test.st b/osmo-st-network/contrib/Test.st new file mode 100644 index 0000000..634ded3 --- /dev/null +++ b/osmo-st-network/contrib/Test.st @@ -0,0 +1,46 @@ +" + (C) 2010 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 . +" +"Test code" + +Eval [ + | socket muxer demuxer data dispatcher ipa | + FileStream fileIn: 'Message.st'. + FileStream fileIn: 'IPAMuxer.st'. + FileStream fileIn: 'IPAConstants.st'. + FileStream fileIn: 'IPADispatcher.st'. + FileStream fileIn: 'IPAProtoHandler.st'. + FileStream fileIn: 'Extensions.st'. + + socket := Sockets.Socket remote: '127.0.0.1' port: 5000. + demuxer := IPADemuxer initOn: socket. + muxer := IPAMuxer initOn: socket. + + dispatcher := IPADispatcher new. + + ipa := IPAProtoHandler new. + dispatcher addHandler: IPAConstants protocolIPA on: ipa with: #handleMsg:. + dispatcher addHandler: IPAConstants protocolMGCP on: ipa with: #handleNoop:. + + [true] whileTrue: [ + [ + data := demuxer next. + data inspect. + dispatcher dispatch: data first with: data second. + ] on: SystemExceptions.EndOfStream do: [:e | ^ false ]. + ] +] diff --git a/osmo-st-network/contrib/m2ua.st b/osmo-st-network/contrib/m2ua.st new file mode 100644 index 0000000..2a70f32 --- /dev/null +++ b/osmo-st-network/contrib/m2ua.st @@ -0,0 +1,19 @@ +Eval [ + | msg dt socket dgram | + + PackageLoader fileInPackage: #Sockets. + PackageLoader fileInPackage: #OsmoNetwork. + msg := Osmo.M2UAMSG fromClass: Osmo.M2UAConstants clsMAUP type: Osmo.M2UAConstants maupData. + msg addTag: (Osmo.M2UATag initWith: Osmo.M2UAConstants tagIdentText data: 'm2ua' asByteArray). + msg addTag: (Osmo.M2UATag initWith: Osmo.M2UAConstants tagData data: #(0 0 0 0 0 0 0 0 0 0) asByteArray). + dt := msg toMessage asByteArray. + + dt inspect. + + socket := Sockets.DatagramSocket new. + dgram := Sockets.Datagram data: dt. + dgram port: 5001. + dgram address: Sockets.SocketAddress loopbackHost. + + socket nextPut: dgram. +] diff --git a/osmo-st-network/core/Extensions.st b/osmo-st-network/core/Extensions.st new file mode 100644 index 0000000..a8ecd52 --- /dev/null +++ b/osmo-st-network/core/Extensions.st @@ -0,0 +1,128 @@ +" + (C) 2010-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 . +" + +Integer extend [ + swap16 [ + | tmp | + + + tmp := self bitAnd: 16rFFFF. + ^ (tmp bitShift: -8) bitOr: ((tmp bitAnd: 16rFF) bitShift: 8) + ] + + swap32 [ + | tmp | + "Certainly not the most effective way" + + + tmp := 0. + tmp := tmp bitOr: ((self bitAnd: 16rFF000000) bitShift: -24). + tmp := tmp bitOr: ((self bitAnd: 16r00FF0000) bitShift: -8). + tmp := tmp bitOr: ((self bitAnd: 16r0000FF00) bitShift: 8). + tmp := tmp bitOr: ((self bitAnd: 16r000000FF) bitShift: 24). + + ^ tmp + ] +] + +Object extend [ + toMessage [ + | msg | + + msg := Osmo.MessageBuffer new. + self writeOn: msg. + ^ msg + ] + + toMessageOrByteArray [ + + ^ self toMessage + ] +] + +ByteArray extend [ + toMessageOrByteArray [ + + ^ self + ] +] + + +"Code from FileDescriptor, GST license" +Sockets.Socket extend [ + nextUshort [ + "Return the next 2 bytes in the byte array, interpreted as a 16 bit unsigned int" + + ^self nextBytes: 2 signed: false + ] + + nextBytes: n signed: signed [ + "Private - Get an integer out of the next anInteger bytes in the stream" + + + | int msb | + int := 0. + 0 to: n * 8 - 16 + by: 8 + do: [:i | int := int + (self nextByte bitShift: i)]. + msb := self nextByte. + (signed and: [msb > 127]) ifTrue: [msb := msb - 256]. + ^int + (msb bitShift: n * 8 - 8) + ] + + nextByte [ + "Return the next byte in the file, or nil at eof" + + + | a | + a := self next. + ^a isNil ifTrue: [a] ifFalse: [a asInteger] + ] +] + +Sockets.StreamSocket extend [ + nextUshort [ + "Return the next 2 bytes in the byte array, interpreted as a 16 bit unsigned int" + + ^self nextBytes: 2 signed: false + ] + + nextBytes: n signed: signed [ + "Private - Get an integer out of the next anInteger bytes in the stream" + + + | int msb | + int := 0. + 0 to: n * 8 - 16 + by: 8 + do: [:i | int := int + (self nextByte bitShift: i)]. + msb := self nextByte. + (signed and: [msb > 127]) ifTrue: [msb := msb - 256]. + ^int + (msb bitShift: n * 8 - 8) + ] + + nextByte [ + "Return the next byte in the file, or nil at eof" + + + | a | + a := self next. + ^a isNil ifTrue: [a] ifFalse: [a asInteger] + ] +] + diff --git a/osmo-st-network/core/ExtensionsGST.st b/osmo-st-network/core/ExtensionsGST.st new file mode 100644 index 0000000..efeec62 --- /dev/null +++ b/osmo-st-network/core/ExtensionsGST.st @@ -0,0 +1,28 @@ +" + (C) 2013 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 . +" + +BlockClosure extend [ + value: arg1 value: arg2 value: arg3 value: arg4 [ + + "Evaluate the receiver passing arg1, arg2, arg3 and arg4 as the parameters" + + + + SystemExceptions.WrongArgumentCount signal + ] +] diff --git a/osmo-st-network/core/LogAreas.st b/osmo-st-network/core/LogAreas.st new file mode 100644 index 0000000..b3ca5a6 --- /dev/null +++ b/osmo-st-network/core/LogAreas.st @@ -0,0 +1,62 @@ +" + (C) 2010-2012 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 . +" + +Osmo.LogArea subclass: LogAreaSCCP [ + + + + LogAreaSCCP class >> areaName [ ^ #sccp ] + LogAreaSCCP class >> areaDescription [ ^ 'SCCP related' ] + LogAreaSCCP class >> default [ + + ^ self new + enabled: true; + minLevel: Osmo.LogLevel debug; + yourself + ] +] + +Osmo.LogArea subclass: LogAreaIPA [ + + + + LogAreaIPA class >> areaName [ ^ #ipa ] + LogAreaIPA class >> areaDescription [ ^ 'IPA related' ] + LogAreaIPA class >> default [ + + ^ self new + enabled: true; + minLevel: Osmo.LogLevel debug; + yourself + ] +] + +Osmo.LogArea subclass: LogAreaM2UA [ + + + + LogAreaM2UA class >> areaName [ ^ #m2ua ] + LogAreaM2UA class >> areaDescription [ ^ 'MTP2 User Adaption' ] + LogAreaM2UA class >> default [ + + ^ self new + enabled: true; + minLevel: Osmo.LogLevel debug; + yourself + ] +] diff --git a/osmo-st-network/core/MessageBuffer.st b/osmo-st-network/core/MessageBuffer.st new file mode 100644 index 0000000..c42ffb0 --- /dev/null +++ b/osmo-st-network/core/MessageBuffer.st @@ -0,0 +1,103 @@ +" + (C) 2010-2012 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 . +" + +Collection subclass: MessageBuffer [ + | chunks | + + + + + MessageBuffer class >> new [ + + ^ (super new) + initialize; + yourself + ] + + initialize [ + + chunks := OrderedCollection new. + ] + + toMessage [ + + ^ self + ] + + prependByteArray: aByteArray [ + + chunks addFirst: aByteArray. + ] + + putByte: aByte [ + + chunks add: (ByteArray with: aByte) + ] + + putByteArray: aByteArray [ + + 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. + high := aInt bitAnd: 16rFF. + data := ByteArray with: low with: high. + chunks add: data. + ] + + putLen32: aInt [ + | a b c d data | + + a := (aInt bitShift: -24) bitAnd: 16rFF. + b := (aInt bitShift: -16) bitAnd: 16rFF. + c := (aInt bitShift: -8) bitAnd: 16rFF. + d := (aInt bitShift: 0) bitAnd: 16rFF. + data := ByteArray with: a with: b with: c with: d. + chunks add: data. + ] + + toByteArray [ + + ^ self asByteArray. + ] + + size [ + "Count of how much data we have collected" + + ^ chunks inject: 0 into: [:acc :each | acc + each size ] + ] + + do: aBlock [ + + chunks do: [:chunk | + chunk do: aBlock. + ]. + ] +] diff --git a/osmo-st-network/core/MessageStructure.st b/osmo-st-network/core/MessageStructure.st new file mode 100644 index 0000000..e62a927 --- /dev/null +++ b/osmo-st-network/core/MessageStructure.st @@ -0,0 +1,451 @@ +" + (C) 2011-2012 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 . +" + +" +The next attempt to generalize the message pattern. We will just describe +messages that have a type, mandatory and optional parameters. The parameters +will be simple ids. There should be code to generate nice parsing routines +" + +Object subclass: TLVDescriptionContainer [ + | type fields | + + + + + TLVDescriptionContainer class >> initWith: aType [ + + ^ self new + instVarNamed: #type put: aType; yourself + ] + + TLVDescriptionContainer class >> findTLVDescription: aType [ + + self allSubclassesDo: [:each | | struct | + struct := each tlvDescription. + struct type = aType ifTrue: [ + ^ struct + ] + ]. + + ^ self error: ('Can not find TLV Description for type: <1p>' expandMacrosWith: aType). + ] + + TLVDescriptionContainer class >> decodeByteStream: aStream type: aType [ + | description | + + "This is a generic decoding method that works by finding the + message structure and then following the structure and will + return an OrderedCollection with tuples." + + description := self findTLVDescription: aType. + ^ description decodeByteStream: aStream. + ] + + TLVDescriptionContainer class >> encodeCollection: aCollection type: aType [ + | description | + + "This is a generic encoding method that will put the collection + onto a MessageBuffer class." + + description := self findTLVDescription: aType. + ^ description encodeCollection: aCollection. + ] + + type: aType [ + + type := aType. + ] + + type [ + + ^ type + ] + + addFixed: aType [ + + self fields add: {#fixed. aType} + ] + + addOptional: aType [ + + self fields add: {#optional. aType} + ] + + addOptionals: aType [ + + "Optional Parameters that may appear more than once." + self fields add: {#optionals. aType} + ] + + addVariable: aType [ + + self fields add: {#variable. aType} + ] + + fields [ + + ^ fields ifNil: [fields := OrderedCollection new] + ] + + fieldsDo: aBlock [ + + ^ self fields do: [:each | aBlock value: each first value: each second] + ] + + filter: aFilter [ + | lst | + + lst := OrderedCollection new. + self fields inject: lst into: [:list :each | + each first = aFilter ifTrue: [ + list add: each second. + ]. + list]. + ^ lst + ] + + filterdDo: aBlock filter: aFilter [ + + ^ self fields do: [:each | + each first = aFilter ifTrue: [ + aBlock value: each first value: each second]]. + ] + + fixed [ + + ^ self filter: #fixed + ] + + fixedDo: aBlock [ + + ^ self filterdDo: aBlock filter: #fixed. + ] + + variable [ + + ^ self filter: #variable + ] + + variableDo: aBlock [ + + ^ self filterdDo: aBlock filter: #variable. + ] + + optional [ + + ^ self filter: #optional + ] + + optionals [ + + ^ self filter: #optionals + ] + + parseFixed: aStream with: aClass into: decoded [ + + decoded add: (aClass readFixedFrom: aStream). + ^ true + ] + + parseField: aStream with: aClass into: decoded [ + | len | + + + "Is this an empty tag" + aClass lengthLength = 0 ifTrue: [ + decoded add: (aClass readVariableFrom: aStream length: 0). + ^ true + ]. + + len := (aStream next: aClass lengthLength) byteAt: 1. + decoded add: (aClass readVariableFrom: aStream length: len). + ^ true + ] + + parseVariable: aStream with: aClass into: decoded [ + + + ^ self parseField: aStream with: aClass into: decoded. + ] + + parseOptional: aStream with: aClass into: decoded [ + | tag len | + + tag := aStream peek. + tag = aClass parameterValue ifFalse: [^ false]. + + aStream skip: 1. + self parseField: aStream with: aClass into: decoded. + ^ true + ] + + parseOptionals: aStream with: aClass into: decoded [ + + + [ + self parseOptional: aStream with: aClass into: decoded. + ] whileTrue: []. + ] + + prepareOptional: aStream [ + + "Nothing to be done here. Subclasses can manipulate the stream" + ] + + decodeByteStream: aStream [ + | decoded first_optional | + + + decoded := OrderedCollection new. + first_optional := true. + self fieldsDo: [:type :clazz | + type = #fixed ifTrue: [ + self parseFixed: aStream with: clazz into: decoded. + ]. + type = #variable ifTrue: [ + self parseVariable: aStream with: clazz into: decoded. + ]. + type = #optional ifTrue: [ + first_optional ifTrue: [first_optional := false. self prepareOptional: aStream]. + self parseOptional: aStream with: clazz into: decoded. + ]. + type = #optionals ifTrue: [ + first_optional ifTrue: [first_optional := false. self prepareOptional: aStream]. + self parseOptionals: aStream with: clazz into: decoded. + ]. + ]. + + "TODO: complain about unfetched bytes?" + ^ decoded + ] + + writeFixed: msg with: clazz from: field state: aState [ + + + (clazz isCompatible: field) ifFalse: [ + ^ self error: + ('Mandatory information must be <1p> but was <2p>.' + expandMacrosWith: clazz with: field). + ]. + + msg nextPutAll: field data. + ] + + writeVariable: msg with: clazz from: field state: aState [ + + + (clazz isCompatible: field) ifFalse: [ + ^ self error: + ('Variable information must be <1p> but was <2p>.' + expandMacrosWith: clazz with: field). + ]. + + "TODO: Respect the lengthLength here" + field class lengthLength > 0 ifTrue: [ + msg nextPut: field data size. + msg nextPutAll: field data. + ] + ] + + writeOptional: msg with: clazz from: field state: aState [ + + + (clazz isCompatible: field) ifFalse: [ + ^ self error: + ('Optional information must be <1p> but was <2p>.' + expandMacrosWith: clazz with: field). + ]. + + "TODO: Respect the lengthLength here" + msg nextPut: field class parameterValue. + field class lengthLength > 0 ifTrue: [ + msg nextPut: field data size. + msg nextPutAll: field data. + ] + ] + + createState [ + + "Subclasses can create their own state to allow jumping in the + stream or leave markers" + ^ nil + ] + + writeFixedEnd: aStream state: aState [ + + "Subclasses can use me to do something at the end of fixed messages." + ] + + writeVariableEnd: aStream state: aState [ + + ] + + encodeCollection: aCollection [ + | stream msg aState | + + + msg := WriteStream on: (ByteArray new: 3). + stream := aCollection readStream. + aState := self createState. + + "Try to match the fields of the TLV description with the fields of + the collection. We keep some local state to check if we are + passed the fixed and variable fields." + + "Write the fixed portion" + self fixedDo: [:type :clazz | + self writeFixed: msg with: clazz from: stream next state: aState. + ]. + self writeFixedEnd: msg state: aState. + + "Write the variable portion" + self variableDo: [:type :clazz | + self writeVariable: msg with: clazz from: stream next state: aState. + ]. + self writeVariableEnd: msg state: aState. + + self fieldsDo: [:type :clazz | + "Check if we are compatible" + (clazz isCompatible: stream peek) ifTrue: [ + type = #optional ifTrue: [ + self writeOptional: msg with: clazz from: stream next state: aState. + ]. + type = #optionals ifTrue: [ + self notYetImplemented + ] + ]. + ]. + + ^ msg contents + ] +] + +Object subclass: MSGField [ + | data | + + + + + MSGField class >> isCompatible: aField [ + + ^ aField isKindOf: self. + ] + + MSGField class >> readVariableFrom: aStream length: aLength [ + + "I verify that I am allowed to read that much and then will read it" + aLength < self octalLength ifTrue: [ + ^ self error: + ('The data is too short. <1p> < <2p>' + expandMacrosWith: aLength with: self octalLength). + ]. + self maxLength ifNotNil: [ + aLength > self maxLength ifTrue: [ + ^ self error: + ('The data is too long <1p> > <2p>.' + expandMacrosWith: aLength with: self maxLength). + ] + ]. + + ^ self new + data: (aStream next: aLength); + yourself + ] + + MSGField class >> parameterName [ + + ^ self subclassResponsibility + ] + + MSGField class >> parameterValue [ + + ^ self subclassResponsibility + ] + + MSGField class >> lengthLength [ + "The length of the length field. The default is to assume a length of + one octet and in the units of octets" + + ^ 1 + ] + + MSGField class >> octalLength [ + + ^ self subclassResponsibility + ] + + MSGField class >> isVarible [ + + "If this field is variable in length" + ^ self subclassResponsibility + ] + + MSGField class >> isFixed [ + + "If this field is of a fixed length" + ^ self subclassResponsibility + ] + + MSGField class >> maxLength [ + + ^ nil + ] + + data: aData [ + + data := aData. + ] + + data [ + + ^ data + ] +] + +MSGField subclass: MSGFixedField [ + + + + MSGFixedField class >> isVarible [ ^ false ] + MSGFixedField class >> isFixed [ ^ true ] + + MSGFixedField class >> readFixedFrom: aStream [ + + ^ self new + data: (aStream next: self octalLength); + yourself + ] + + MSGFixedField class >> readVariableFrom: aStream length: aLength [ + + aLength = self octalLength ifFalse: [ + ^ self error: 'The size needs to be exact'. + ]. + + ^ super readVariableFrom: aStream length: aLength + ] +] + +MSGField subclass: MSGVariableField [ + + + + MSGVariableField class >> isVarible [ ^ true ] + MSGVariableField class >> isFixed [ ^ false ] +] diff --git a/osmo-st-network/core/TLV.st b/osmo-st-network/core/TLV.st new file mode 100644 index 0000000..f15b29f --- /dev/null +++ b/osmo-st-network/core/TLV.st @@ -0,0 +1,304 @@ +" + (C) 2012-2014 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: TLVDescription [ + | tag kind parse_class type inst_var min_size max_size len_size force_tag | + + + + TLVDescription class [ + optional [ + + ^ #optional + ] + + mandatory [ + + ^ #mandatory + ] + + conditional [ + + ^ #conditional + ] + + tagLengthValue [ + + ^ #tlv + ] + + tagValue [ + + ^ #tv + ] + + valueOnly [ + + ^ #valueOnly + ] + + tagOnly [ + + ^ #tagOnly + ] + + lengthValue [ + + ^#lv + ] + + new [ + + ^ super basicNew + initialize; + yourself + ] + ] + + initialize [ + + kind := self class mandatory. + type := self class tagLengthValue. + len_size := 1. + force_tag := false. + ] + + tag: aTag [ + + tag := aTag + ] + + tag [ + + "The tag value for this tag inside the bytestream" + ^ tag + ] + + minSize: aMin maxSize: aMax [ + + "This only makes sense for *LV elements" + min_size := aMin. + max_size := aMax. + ] + + minSize: aMin [ + min_size := aMin. + max_size := nil. + ] + + valueSize: aSize [ + + ^ self minSize: aSize maxSize: aSize. + ] + + valueSize [ + ^ max_size + ] + + isOptional [ + + ^ kind = self class optional + ] + + isMandatory [ + + ^ kind = self class mandatory + ] + + isConditional [ + + ^ kind = self class conditional + ] + + isFixedSize [ + + ^ type = self class tagValue or: [type = self class valueOnly]. + ] + + hasLength [ + + ^ type = self class tagLengthValue or: [type = self class lengthValue] + ] + + isLen16 [ + + ^ self hasLength and: [len_size = 2] + ] + + isLen8 [ + + ^ self hasLength and: [len_size = 1] + ] + + isForcedTag [ + + ^ force_tag + ] + + hasTag [ + + ^type ~= self class lengthValue and: [type ~= self class valueOnly] + ] + + needsTag [ + + ^force_tag or: [self hasTag and: [self isOptional or: [self isConditional]]]. + ] + + presenceKind: aKind [ + + "Is this required, optional, variable?" + kind := aKind + ] + + beOptional [ + + self presenceKind: self class optional. + ] + + beConditional [ + + self presenceKind: self class conditional. + ] + + beForceTagged [ + + "Write a tag even if this element is mandatory" + force_tag := true. + ] + + beTagOnly [ + + self typeKind: self class tagOnly. + ] + + beTV [ + + self typeKind: self class tagValue + ] + + beTLV [ + + self typeKind: self class tagLengthValue + ] + + beLV [ + + self typeKind: self class lengthValue + ] + + beLen16 [ + + len_size := 2. + ] + + typeKind: aType [ + + type := aType + ] + + typeKind [ + + ^ type + ] + + parseClass: aClass [ + + "The class to be used to parse this" + parse_class := aClass + ] + + parseClass [ + + ^ parse_class + ] + + instVarName: aName [ + + inst_var := aName + ] + + instVarName [ + + ^ inst_var + ] +] + +Object subclass: TLVParserBase [ + + + + parseMandatory: attr tag: aTag stream: aStream [ + + aTag = attr tag + ifFalse: [^self error: + ('Mandatory <1p> element is missing' + expandMacrosWith: attr instVarName).]. + aStream skip: 1. + + self doParse: attr stream: aStream. + ] + + parseConditional: attr tag: aTag stream: aStream [ + + ^ self parseOptional: attr tag: aTag stream: aStream + ] + + parseOptional: attr tag: aTag stream: aStream [ + + aTag = attr tag + ifFalse: [^false]. + + aStream skip: 1. + self doParse: attr stream: aStream. + ] + + doParse: attr stream: aStream [ + + attr parseClass isNil + ifTrue: [^self error: 'No parse class available']. + + self instVarNamed: attr instVarName + put: (attr parseClass readFrom: aStream with: attr). + ^ true + ] + + writeOn: aMsg [ + + + "Write the header" + self writeHeaderOn: aMsg. + + "Write each element" + self class tlvDescription do: [:attr | + | val | + val := self instVarNamed: attr instVarName. + + "Check if it may be nil" + (val isNil and: [attr isMandatory]) + ifTrue: [^self error: 'Mandatory parameter is nil.']. + + "Now write it" + val isNil ifFalse: [ + attr needsTag ifTrue: [aMsg putByte: attr tag]. + val writeOn: aMsg with: attr. + ]. + ] + ] +] diff --git a/osmo-st-network/core/TLVTests.st b/osmo-st-network/core/TLVTests.st new file mode 100644 index 0000000..944b535 --- /dev/null +++ b/osmo-st-network/core/TLVTests.st @@ -0,0 +1,73 @@ +" + (C) 2012,2014 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: TLVDescriptionTest [ + + + + testTLVCreation [ + | tlv | + + "Test default" + tlv := TLVDescription new. + self + assert: tlv isMandatory; + deny: tlv isOptional. + + "Test update" + tlv presenceKind: tlv class optional. + self + assert: tlv isOptional; + deny: tlv isMandatory. + + tlv instVarName: #bla. + self assert: tlv instVarName = #bla. + + tlv tag: 16r23. + self assert: tlv tag = 16r23. + + tlv beLV. + self + assert: tlv typeKind equals: #lv; + assert: tlv hasLength; + deny: tlv hasTag. + + tlv beTLV. + self + assert: tlv typeKind equals: #tlv; + assert: tlv hasLength; + assert: tlv hasTag. + + tlv beTagOnly. + self + assert: tlv typeKind equals: #tagOnly; + assert: tlv hasTag; + deny: tlv hasLength. + ] + + testNeedsTag [ + | tlv | + tlv := TLVDescription new + tag: 16r23; + beTV; + beConditional; + yourself. + + self assert: tlv needsTag. + ] +] diff --git a/osmo-st-network/ipa/IPAConstants.st b/osmo-st-network/ipa/IPAConstants.st new file mode 100644 index 0000000..1e8ab40 --- /dev/null +++ b/osmo-st-network/ipa/IPAConstants.st @@ -0,0 +1,65 @@ +" + (C) 2010-2012 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: IPAConstants [ + + + + IPAConstants class >> protocolRSL [ ^ 16r00 ] + IPAConstants class >> protocolMGCP [ ^ 16rFC ] + IPAConstants class >> protocolSCCP [ ^ 16rFD ] + IPAConstants class >> protocolIPA [ ^ 16rFE ] + IPAConstants class >> protocolOML [ ^ 16rFF ] + IPAConstants class >> protocolOSMO [ ^ 16rEE ] + + IPAConstants class >> msgPing [ ^ 16r00 ] + IPAConstants class >> msgPong [ ^ 16r01 ] + IPAConstants class >> msgIdGet [ ^ 16r04 ] + IPAConstants class >> msgIdResp [ ^ 16r05 ] + IPAConstants class >> msgIdAck [ ^ 16r06 ] + IPAConstants class >> msgSCCP [ ^ 16rFF ] + + IPAConstants class >> idtagSernr [ ^ 16r00 ] + IPAConstants class >> idtagUnitName [ ^ 16r01 ] + IPAConstants class >> idtagLocation1 [ ^ 16r02 ] + IPAConstants class >> idtagLocation2 [ ^ 16r03 ] + IPAConstants class >> idtagEquipVer [ ^ 16r04 ] + IPAConstants class >> idtagSwVersion [ ^ 16r05 ] + IPAConstants class >> idtagIpaddr [ ^ 16r06 ] + IPAConstants class >> idtagMacaddr [ ^ 16r07 ] + IPAConstants class >> idtagUnit [ ^ 16r08 ] + + IPAConstants class >> osmoCtrl [ ^ 16r00 ] + IPAConstants class >> osmoMgcp [ ^ 16r01 ] + IPAConstants class >> osmoLac [ ^ 16r02 ] + + IPAConstants class >> protocolOsmoCTRL [ + + ^ {self protocolOSMO. self osmoCtrl} + ] + + IPAConstants class >> protocolOsmoMGCP [ + + ^ {self protocolOSMO. self osmoMgcp} + ] + + IPAConstants class >> protocolOsmoLAC [ + + ^ {self protocolOSMO. self osmoLac} + ] +] diff --git a/osmo-st-network/ipa/IPAConstantsGST.st b/osmo-st-network/ipa/IPAConstantsGST.st new file mode 100644 index 0000000..b869005 --- /dev/null +++ b/osmo-st-network/ipa/IPAConstantsGST.st @@ -0,0 +1,77 @@ +" + (C) 2010-2013 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 . +" + +CCompound subclass: CPackedStruct [ + + + + + CPackedStruct class >> declaration: array [ + "Compile methods that implement the declaration in array." + + + self + declaration: array + inject: self superclass sizeof + into: [:oldOffset :alignment | oldOffset] + ] + + CPackedStruct class >> compileSize: size align: alignment [ + + ^ super compileSize: size align: 1. + ] +] + +CPackedStruct subclass: IPASCCPState [ + + + + + + srcAddr [ + + ^ SCCPAddrReference fromCData: self src. + ] + + dstAddr [ + + ^ SCCPAddrReference fromCData: self dst. + ] + + imsiString [ + "We will need to count how many chars of the array are used" + + + 0 to: 16 do: [:index | | c | + c := self imsi at: index. + c = (Character value: 0) + ifTrue: [ + ^ String fromCData: self imsi size: index. + ]. + ]. + + ^ String fromCData: self imsi. + ] +] diff --git a/osmo-st-network/ipa/IPADispatcher.st b/osmo-st-network/ipa/IPADispatcher.st new file mode 100644 index 0000000..cfe918a --- /dev/null +++ b/osmo-st-network/ipa/IPADispatcher.st @@ -0,0 +1,58 @@ +" + (C) 2010 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: IPADispatcher [ + | handlers | + + + + + IPADispatcher class >> new [ + + ^ super new + initialize; + yourself + ] + + initialize [ + + handlers := Dictionary new. + ] + + addHandler: aStream on: anObject with: aSelector [ + + handlers at: aStream put: [:msg | anObject perform: aSelector with: msg]. + ] + + addHandler: aStream on: aBlock [ + + handlers at: aStream put: aBlock. + ] + + dispatch: aStream with: aData [ + | handler | + + handler := handlers at: aStream ifAbsent: [ + self logError: ('IPADispatcher has no registered handler for <1p>' + expandMacrosWith: aStream) area: #ipa. + ^ false + ]. + + handler value: aData. + ] +] diff --git a/osmo-st-network/ipa/IPAMsg.st b/osmo-st-network/ipa/IPAMsg.st new file mode 100644 index 0000000..36833df --- /dev/null +++ b/osmo-st-network/ipa/IPAMsg.st @@ -0,0 +1,193 @@ +" + (C) 2012 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: IPAMsgRequest [ + | data type | + + + + + IPAMsgRequest class >> parse: aStream [ + | type data | + + "TLV parser for the IPAMessage" + + type := aStream next. + data := self parseTLV: aStream. + + ^ self new + type: type; + data: data; + yourself. + ] + + IPAMsgRequest class >> parseTLV: aStream [ + | data | + + data := OrderedCollection new. + + [aStream atEnd] whileFalse: [ + | len tag msg | + len := aStream next. + tag := aStream next. + + "On requests the length counts the tag" + msg := len > 1 + ifTrue: [aStream next: len] + ifFalse: [nil]. + + data add: (Association key: tag value: msg) + ]. + + ^ data + ] + + type: aType [ + + type := aType. + ] + + data: aData [ + + data := aData. + ] + + tags [ + + ^ data collect: [:each | each key]. + ] + + hasTag: aTag [ + + ^ self tags includes: aTag + ] + + dataForTag: aTag [ + + data do: [:each | each key = aTag ifTrue: [^each value]]. + + ^ SystemExceptions.NotFound + signalOn: self what: 'Tag ', aTag asString, ' not found'. + ] + + writeOn: aMsg [ + + aMsg putByte: type. + + self writeTLV: aMsg. + ] + + writeTLV: aMsg [ + + + data do: [:each | + "Write the length and tag" + aMsg + putByte: 1 + each value basicSize; + putByte: each key. + + "Write the optional value" + each value isNil ifFalse: [ + aMsg putByteArray: each value.]. + ]. + ] +] + +IPAMsgRequest subclass: IPAMsgResponse [ + + + + + IPAMsgResponse class >> parse: aStream [ + | type data | + + "TLV parser for the IPAMessage" + + type := aStream next. + aStream skip: 1. + data := self parseTLV: aStream. + + ^ self new + type: type; + data: data; + yourself. + ] + + IPAMsgResponse class >> readByteString: aStream length: aLen [ + "Read a IPA string from a stream that might be up to len." + | str | + str := WriteStream on: (ByteArray new: aLen). + + (1 to: aLen) do: [:each | + | chr | + + chr := aStream next. + str nextPut: chr. + + "deal with broken messages. so far only observed at the end + of a packet" + (aStream atEnd and: [chr = 16r0]) + ifTrue: [^ str contents]. + ]. + + ^ str contents. + ] + + IPAMsgResponse class >> parseTLV: aStream [ + | data | + "The messages generated by the ip.access nanoBTS do not follow + the TLV pattern properly. For responses the length does not include + the size of the tag and to make it worse sometimes the wrong size + is sent, e.g. there strings are null-terminated." + + data := OrderedCollection new. + + [aStream atEnd] whileFalse: [ + | tag len string | + len := aStream next. + tag := aStream next. + string := self readByteString: aStream length: len. + + data add: (Association key: tag value: string). + ]. + + ^ data + ] + + writeOn: aMsg [ + + + aMsg putByte: type. + aMsg putByte: 0. + self writeTLV: aMsg. + ] + + writeTLV: aMsg [ + + "Request/Response appear to have different size constraints" + + data do: [:each | + "Write the length and tag" + aMsg + putByte: each value basicSize; + putByte: each key; + putByteArray: each value. + ]. + ] +] diff --git a/osmo-st-network/ipa/IPAMuxer.st b/osmo-st-network/ipa/IPAMuxer.st new file mode 100644 index 0000000..c0f45ca --- /dev/null +++ b/osmo-st-network/ipa/IPAMuxer.st @@ -0,0 +1,108 @@ +" + (C) 2010-2012 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: IPADemuxer [ + | socket | + + + + + IPADemuxer class >> initOn: aSocket [ + + ^ (self new) + socket: aSocket; + yourself. + ] + + next [ + "Return a tuple of stream and bytearray" + + + | size stream data | + + size := socket nextUshort swap16. + stream := socket nextByte. + data := socket next: size. + + "I know about extensions. Check if this is..." + stream = IPAConstants protocolOSMO ifTrue: [ + stream := Array with: stream with: data first asInteger. + data := data allButFirst. + ]. + + ^ Array with: stream with: data. + ] + + socket: aSocket [ + + socket := aSocket. + ] +] + +Object subclass: IPAMuxer [ + | socket | + + + + + IPAMuxer class >> initOn: aSocket [ + + ^ (self new) + socket: aSocket; + yourself. + ] + + prepareNext: aData with: aStream [ + "Write the data onto the stream" + | msg | + + + aData size > 65535 + ifTrue: [ + self logError: 'Too much data' area: #ipa. + self error: 'Too much data'. + ]. + + msg := MessageBuffer new. + + aStream isArray + ifTrue: [ + msg putLen16: aData size + aStream size - 1. + msg putByteArray: aStream asByteArray] + ifFalse: [ + msg putLen16: aData size. + msg putByte: aStream]. + + msg putByteArray: aData. + + ^ msg asByteArray. + ] + + nextPut: aData with: aStream [ + + socket nextPut: (self prepareNext: aData with: aStream). + ] + + socket: aSocket [ + + socket := aSocket. + ] +] diff --git a/osmo-st-network/ipa/IPAProtoHandler.st b/osmo-st-network/ipa/IPAProtoHandler.st new file mode 100644 index 0000000..a705d3b --- /dev/null +++ b/osmo-st-network/ipa/IPAProtoHandler.st @@ -0,0 +1,108 @@ +" + (C) 2010-2012 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: IPAProtoHandler [ + | token muxer | + + + + + IPAProtoHandler class [ + | handlers | + + initialize [ + + ^ self initializeHandlers + ] + ] + + IPAProtoHandler class >> initializeHandlers [ + + (handlers := Dictionary new) + at: IPAConstants msgPing put: #handlePing:; + at: IPAConstants msgPong put: #handlePong:; + at: IPAConstants msgIdGet put: #handleIdGet:; + at: IPAConstants msgIdAck put: #handleIdAck:. + ] + + IPAProtoHandler class >> handlers [ + ^ handlers ifNil: [self initialize. handlers]. + ] + + registerOn: aDispatcher [ + + aDispatcher addHandler: IPAConstants protocolIPA on: self with: #handleMsg:. + ] + + muxer: aMuxer [ + + muxer := aMuxer. + ] + + token: aToken [ + + token := aToken. + ] + + handleMsg: aMsg [ + | selector | + + + selector := self class handlers at: (aMsg first asInteger) ifAbsent: [ + self logError: 'IPA message not understood ', aMsg first asInteger asString + area: #ipa. + ^ false + ]. + + self perform: selector with: aMsg. + ] + + handlePing: aMsg [ + + muxer nextPut: (ByteArray with: IPAConstants msgPong) with: IPAConstants protocolIPA. + ] + + handlePong: aMsg [ + + self logDebug: 'PONG' area: #ipa. + ] + + handleIdGet: aMsg [ + | msg | + + + msg := MessageBuffer new. + msg putByte: IPAConstants msgIdResp. + msg putLen16: token size + 1. + msg putByte: IPAConstants idtagUnitName. + msg putByteArray: token asByteArray. + + muxer nextPut: msg asByteArray with: IPAConstants protocolIPA. + ] + + handleIdAck: aMsg [ + + self logDebug: 'ID ACK' area: #ipa. + ] +] + +Eval [ + IPAProtoHandler initialize. +] diff --git a/osmo-st-network/ipa/IPATests.st b/osmo-st-network/ipa/IPATests.st new file mode 100644 index 0000000..97f86cc --- /dev/null +++ b/osmo-st-network/ipa/IPATests.st @@ -0,0 +1,160 @@ +" + (C) 2010-2012 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: IPATests [ + | called | + + + + IPATests class >> packageNamesUnderTest [ + + ^ #('OsmoNetwork') + ] + + testMux [ + | data mux | + mux := IPAMuxer new. + + data := { + {mux prepareNext: #(1 2 3) with: IPAConstants protocolOML. + #(0 3 255 1 2 3) asByteArray}. + + {mux prepareNext: #(1 2 3) with: IPAConstants protocolOsmoMGCP. + #(0 4 238 1 1 2 3) asByteArray}. + }. + + data do: [:each | + self assert: each first = each second.] + ] + + testDispatch [ + | dispatch | + + + called := false. + dispatch := IPADispatcher new + addHandler: 16r23 on: self with: #dispatchcallback:; + yourself. + dispatch dispatch: 16r23 with: 'data'. + self assert: called. + + called := false. + dispatch + addHandler: 16r42 on: [:msg | called := msg = 'data' ]; + dispatch: 16r42 with: 'data'. + self assert: called. + ] + + dispatchcallback: aData [ + + called := aData = 'data'. + ] +] + +TestCase subclass: IPAMsgTests [ + + + IPAMsgTests class >> parseOnlyData [ + ^ Array + with: IPAMsgResponse->#(16r05 16r00 16r0A 16r08 16r31 16r38 16r30 16r31 + 16r2F 16r30 16r2F 16r30 16r00 16r00 16r13 16r07 + 16r30 16r30 16r3A 16r30 16r32 16r3A 16r39 16r35 + 16r3A 16r30 16r30 16r3A 16r34 16r30 16r3A 16r36 + 16r34 16r00 16r00 16r02 16r02 16r00 16r00 16r0D + 16r03 16r42 16r54 16r53 16r5F 16r4E 16r42 16r54 + 16r31 16r33 16r31 16r47 16r00 16r00 16r0C 16r04 + 16r31 16r36 16r35 16r61 16r30 16r32 16r39 16r5F + 16r35 16r35 16r00 16r00 16r14 16r05 16r31 16r36 + 16r38 16r64 16r34 16r37 16r32 16r5F 16r76 16r32 + 16r30 16r30 16r62 16r31 16r34 16r33 16r64 16r30 + 16r00 16r00 16r18 16r01 16r6E 16r62 16r74 16r73 + 16r2D 16r30 16r30 16r2D 16r30 16r32 16r2D 16r39 + 16r35 16r2D 16r30 16r30 16r2D 16r34 16r30 16r2D + 16r36 16r34 16r00 16r00 16r0A 16r00 16r30 16r30 + 16r31 16r30 16r32 16r37 16r32 16r39 16r00). + ] + + IPAMsgTests class >> data [ + + ^ Array + with: IPAMsgRequest->#(16r04 16r01 16r08 16r01 16r07 16r01 16r02 16r01 + 16r03 16r01 16r04 16r01 16r05 16r01 16r01 16r01 + 16r00) + with: IPAMsgResponse->#(16r05 16r00 16r04 16r01 16r31 16r38 16r30 16r31) + ] + + testMsgDissect [ + + self class data do: [:test_data | | msg stream | + stream := test_data value readStream. + msg := test_data key parse: stream. + + self + assert: stream atEnd; + assert: msg toMessage asByteArray = test_data value asByteArray; + should: [msg dataForTag: 9] raise: SystemExceptions.NotFound; + deny: (msg hasTag: 9). + ] + ] + + testMsgInputStrict [ + | test_data msg stream | + test_data := self class data first. + stream := test_data value readStream. + msg := test_data key parse: stream. + + self + assert: stream atEnd; + assert: msg tags = #(8 7 2 3 4 5 1 0) asOrderedCollection; + assert: (msg hasTag: 8); + assert: (msg dataForTag: 8) = nil. + ] + + testParseOnly [ + "This tests that parsing a 'malformed' response will actually + work, generating the response will be different though." + + self class parseOnlyData do: [:test_data | | msg stream | + stream := test_data value readStream. + msg := test_data key parse: stream. + + self + assert: stream atEnd; + assert: (msg hasTag: 16r0); + assert: (msg hasTag: 16r1); + assert: (msg hasTag: 16r2); + assert: (msg hasTag: 16r3); + assert: (msg hasTag: 16r4); + assert: (msg hasTag: 16r5); + assert: (msg hasTag: 16r7); + assert: (msg hasTag: 16r8); + deny: (msg hasTag: 16rA); + assert: (msg dataForTag: 16r0) = #(16r30 16r30 16r31 16r30 16r32 16r37 16r32 16r39 16r0) asByteArray. + ] + ] +] + + +TestCase subclass: IPAGSTTests [ + + + testSize [ + self assert: IPASCCPState sizeof = 25. + ] +] + diff --git a/osmo-st-network/isup/ISUP.st b/osmo-st-network/isup/ISUP.st new file mode 100644 index 0000000..1808c9e --- /dev/null +++ b/osmo-st-network/isup/ISUP.st @@ -0,0 +1,472 @@ +" + (C) 2011-2012 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: ISUPConstants [ + + + + ISUPConstants class [ + msgAPT [ + "Application transport" + + ^ 2r01000001 + ] + + msgACM [ + "Address complete" + ^ 2r00000110 + ] + + msgAMN [ + "Answer" + ^ 2r00001001 + ] + + msgBLA [ + "Blocking acknowledgement" + ^ 2r00010101 + ] + + msgBLO [ + "Blocking" + ^ 2r00010011 + ] + + msgCCR [ + "Continuity check request" + ^ 2r00010001 + ] + + msgCFN [ + "Confusion" + ^ 2r00101111 + ] + + msgCGB [ + "Circuit group blocking" + ^ 2r00011000 + ] + + msgCGBA [ + "Circuit group blocking acknowledgement" + ^ 2r00011010 + ] + + msgCGU [ + "Circuit group unblocking" + ^ 2r00011001 + ] + + msgCGUA [ + "Circuit group unblocking acknowledgement" + ^ 2r00011011 + ] + + msgCON [ + "Connect" + ^ 2r00000111 + ] + + msgCOT [ + "Continuity" + ^ 2r00000101 + ] + + msgCPG [ + "Call progress" + ^ 2r00101100 + ] + + msgCRG [ + "Charge information" + ^ 2r00110001 + ] + + msgCQM [ + "Circuit group query" + ^ 2r00101010 + ] + + msgCQR [ + "Circuit group query response" + ^ 2r00101011 + ] + + msgDRS [ + "Delayed release (reserved – used in 1988 version)" + ^ 2r00100111 + ] + + msgFAC [ + "Facility" + ^ 2r00110011 + ] + + msgFAA [ + "Facility accepted" + ^ 2r00100000 + ] + + msgFAR [ + "Facility request" + ^ 2r00011111 + ] + + msgFOT [ + "Forward transfer" + ^ 2r00001000 + ] + + msgFRJ [ + "Facility reject" + ^ 2r00100001 + ] + + msgGRA [ + "Circuit group reset acknowledgement" + ^ 2r00101001 + ] + + msgGRS [ + "Circuit group reset" + ^ 2r00010111 + ] + + msgIDR [ + "Identification request" + ^ 2r00110110 + ] + + msgIDS [ + "Identification response" + ^ 2r00110111 + ] + + msgIAM [ + "Initial address" + ^ 2r00000001 + ] + + msgINF [ + "Information" + ^ 2r00000100 + ] + + msgINR [ + "Information request" + ^ 2r00000011 + ] + + msgLPA [ + "Loop back acknowledgement" + ^ 2r00100100 + ] + + msgLPR [ + "Loop prevention" + ^ 2r01000000 + ] + + msgOLM [ + "Overload" + ^ 2r00110000 + ] + + msgPAM [ + "Pass-along" + ^ 2r00101000 + ] + + msgREL [ + "Release" + ^ 2r00001100 + ] + + msgRES [ + "Resume" + ^ 2r00001110 + ] + + msgRLC [ + "Release complete" + ^ 2r00010000 + ] + + msgRSC [ + "Reset circuit" + ^ 2r00010010 + ] + + msgSAM [ + "Subsequent address" + ^ 2r00000010 + ] + + msgSUS [ + "Suspend" + ^ 2r00001101 + ] + + msgUBL [ + "Unblocking" + ^ 2r00010100 + ] + + msgUBA [ + "Unblocking acknowledgement" + ^ 2r00010110 + ] + + msgUCIC [ + "Unequipped circuit identification code" + ^ 2r00101110 + ] + + msgUSR [ + "User-to-user information" + ^ 2r00101101 + ] + + msgNRM [ + "Network resource management" + ^ 2r00110010 + ] + + msgPRI [ + "Pre-release information" + ^ 2r01000010 + ] + + msgSAN [ + "Subsequent Directory Number" + ^ 2r01000011 + ] + + msgSEG [ + "Segmentation" + ^ 2r00111000 + ] + + msgUPA [ + "User Part available" + ^ 2r00110100 + ] + + msgUPT [ + "User Part test" + ^ 2r00110100 + ] + + + parAccessDeliveryInformation [ ^ 2r00101110 ] + parAccessTransport [ ^ 2r00000011 ] + parApplicationTransportParameter [ ^ 2r01111000 ] + parAutomaticCongestionLevel [ ^ 2r00100111 ] + parBackwardCallIndicators [ ^ 2r00010001 ] + parBackwardGVNS [ ^ 2r01001101 ] + parCallDiversionInformation [ ^ 2r00110110 ] + parCallDiversionTreatmentIndicators [ ^ 2r01101110 ] + parCallHistoryInformation [ ^ 2r00101101 ] + parCallOfferingTreatmentIndicators [ ^ 2r01110000 ] + parCallReference [ ^ 2r00000001 ] + parCallTransferNumber [ ^ 2r01000101 ] + parCallTransferReference [ ^ 2r01000011 ] + parCalledINNumber [ ^ 2r01101111 ] + parCalledDirectoryNumber [ ^ 2r01111101 ] + parCalledPartyNumber [ ^ 2r00000100 ] + parCallingGeodeticLocation [ ^ 2r10000001 ] + parCallingPartyNumber [ ^ 2r00001010 ] + parCallingPartysCategory [ ^ 2r00001001 ] + parCauseIndicators [ ^ 2r00010010 ] + parCCNRPossibleIndicator [ ^ 2r01111010 ] + parCCSS [ ^ 2r01001011 ] + parChargedPartyIdentification [ ^ 2r01110001 ] + parCircuitAssignmentMap [ ^ 2r00100101 ] + parCircuitGroupSupervisionMessageType [ ^ 2r00010101 ] + parCircuitStateIndicator [ ^ 2r00100110 ] + parClosedUserGroupInterlockCode [ ^ 2r00011010 ] + parCollectCallRequest [ ^ 2r01111001 ] + parConferenceTreatmentIndicators [ ^ 2r01110010 ] + parConnectedNumber [ ^ 2r00100001 ] + parConnectionRequest [ ^ 2r00001101 ] + parContinuityIndicators [ ^ 2r00010000 ] + parCorrelationId [ ^ 2r01100101 ] + parDisplayInformation [ ^ 2r01110011 ] + parEchoControlInformation [ ^ 2r00110111 ] + parEndOfOptionalParameters [ ^ 2r00000000 ] + parEventInformation [ ^ 2r00100100 ] + parFacilityIndicator [ ^ 2r00011000 ] + parForwardCallIndicators [ ^ 2r00000111 ] + parForwardGVNS [ ^ 2r01001100 ] + parGenericDigits [ ^ 2r11000001 ] + parGenericNotificationIndicator [ ^ 2r00101100 ] + parGenericNumber [ ^ 2r11000000 ] + parGenericReference [ ^ 2r10000010 ] + parHTRInformation [ ^ 2r10000010 ] + parHopCounter [ ^ 2r00111101 ] + parInformationIndicators [ ^ 2r00001111 ] + parInformationRequestIndicators [ ^ 2r00001110 ] + parLocationNumber [ ^ 2r00111111 ] + parLoopPreventionIndicators [ ^ 2r01000100 ] + parMCIDRequestIndicators [ ^ 2r00111011 ] + parMCIDResponseIndicators [ ^ 2r00111100 ] + parMessageCompatibilityInformation [ ^ 2r00111000 ] + parMLPPPrecedence [ ^ 2r00111010 ] + parNatureOfConnectionIndicators [ ^ 2r00000110 ] + parNetworkManagementControls [ ^ 2r01011011 ] + parNetworkRoutingNumber [ ^ 2r10000100 ] + parNetworkSpecificFacility [ ^ 2r00101111 ] + parNumberPortabilityForwardInformation [ ^ 2r10001101 ] + parOptionalBackwardCallIndicators [ ^ 2r00101001 ] + parOptionalForwardCallIndicators [ ^ 2r00001000 ] + parOriginalCalledNumber [ ^ 2r00101000 ] + parOriginalCalledINNumber [ ^ 2r01111111 ] + parOriginationISCPointCode [ ^ 2r00101011 ] + parParameterCompatibilityInformation [ ^ 2r00111001 ] + parPivotCapability [ ^ 2r01111011 ] + parPivotCounter [ ^ 2r10000111 ] + parPivotRoutingBackwardInformation [ ^ 2r10001001 ] + parPivotRoutingForwardInformation [ ^ 2r10001000 ] + parPivotRoutingIndicators [ ^ 2r01111100 ] + parPivotStatus [ ^ 2r10000110 ] + parPropagationDelayCounter [ ^ 2r00110001 ] + parQoRCapability [ ^ 2r10000101 ] + parRange [ ^ 2r00010110 ] + parRangeAndStatus [ ^ 2r00010110 ] + parRedirectBackwardInformation [ ^ 2r10001100 ] + parRedirectCapability [ ^ 2r01001110 ] + parRedirectCounter [ ^ 2r01110111 ] + parRedirectForwardInformation [ ^ 2r10001011 ] + parRedirectStatus [ ^ 2r10001010 ] + parRedirectingNumber [ ^ 2r00001011 ] + parRedirectionInformation [ ^ 2r00010011 ] + parRedirectionNumber [ ^ 2r00001100 ] + parRedirectionNumberRestriction [ ^ 2r01000000 ] + parRemoteOperations [ ^ 2r00110010 ] + parSCFId [ ^ 2r01100110 ] + parServiceActivation [ ^ 2r00110011 ] + parSignallingPointCode [ ^ 2r00011110 ] + parSubsequentNumber [ ^ 2r00000101 ] + parSuspendResumeIndicators [ ^ 2r00100010 ] + parTransitNetworkSelection [ ^ 2r00100011 ] + parTransmissionMediumRequirement [ ^ 2r00000010 ] + parTransmissionMediumRequirementPrime [ ^ 2r00111110 ] + parTransmissionMediumUsed [ ^ 2r00110101 ] + parUIDActionIndicators [ ^ 2r01110100 ] + parUIDCapabilityIndicators [ ^ 2r01110101 ] + parUserServiceInformation [ ^ 2r00011101 ] + parUserServiceInformationPrime [ ^ 2r00110000 ] + parUserTeleserviceInformation [ ^ 2r00110100 ] + parUserToUserIndicators [ ^ 2r00101010 ] + parUserToUserInformation [ ^ 2r00100000 ] + + addrNAT_NATIONAL [ + "National (significant) number" + + ^ 2r0000011 + ] + + addrNAT_INTERNATIONAL [ + "International number" + + ^ 2r0000100 + ] + ] +] + +TLVDescriptionContainer 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. + ptr := aStream next. + + aStream skip: ptr - 1. + res := super parseVariable: aStream with: aClass into: decoded. + aStream position: pos + 1. + + ^ res + ] + + prepareOptional: aStream [ + "We are done with the variable section and now get the pointer + to the optional part and will move the stream there." + + + | pos ptr | + pos := aStream position. + ptr := aStream next. + aStream skip: ptr - 1. + ] + + writeVariableEnd: aStream state: aState [ + + + "Write the optional pointer. TODO: In case of no optional this + should be 0" + aStream nextPut: (aState at: 'data') size + 1. + aStream nextPutAll: (aState at: 'data') contents. + ] + + writeVariable: msg with: clazz from: field state: aState [ + | var_len | + "We will write a pointer and then store the data in the state" + + + "Write the pointer of where the data will be" + var_len := self variable size. + msg nextPut: (aState at: 'data') size + var_len + 1. + + "Store the data for later" + super writeVariable: (aState at: 'data') with: clazz from: field state: nil. + ] + + createState [ + "Our parsing state. We need to queue the variable fields until all + of them have been written." + + ^ Dictionary from: {'data' -> (WriteStream on: (ByteArray new: 3))}. + ] +] + diff --git a/osmo-st-network/isup/ISUPExtensions.st b/osmo-st-network/isup/ISUPExtensions.st new file mode 100644 index 0000000..7c138e7 --- /dev/null +++ b/osmo-st-network/isup/ISUPExtensions.st @@ -0,0 +1,99 @@ +" + (C) 2012 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 . +" + +ISUPNatureOfConnectionIndicators class extend [ + satNoSat [ ^ 2r00 ] + satOneSat [ ^ 2r01 ] + satTwoSat [ ^ 2r10 ] + satSpare [ ^ 2r11 ] + + cciNotRequired [ ^ 2r00 ] + cciRequired [ ^ 2r01 ] + cciPerformed [ ^ 2r10 ] + cciSpare [ ^ 2r11 ] + + ecdiNotIncluded [ ^ 2r0 ] + ecdiIncluded [ ^ 2r1 ] +] + +ISUPCallingPartysCategory class extend [ + callingSubscriberWithPriority [ + + ^2r1011 + ] + + categoryUnknown [ + + ^2r0 + ] + + dataCall [ + + ^2r1100 + ] + + operatorLanguageEnglish [ + + ^2r10 + ] + + operatorLanguageFrench [ + + ^2r1 + ] + + operatorLanguageGerman [ + + ^2r11 + ] + + operatorLanguageRussian [ + + ^2r100 + ] + + operatorLanguageSpanish [ + + ^2r101 + ] + + ordinarySubscriber [ + + ^2r1010 + ] + + payphone [ + + ^2r1111 + ] + + reserved [ + + ^2r1001 + ] + + spare [ + + ^2r1110 + ] + + testCall [ + + ^2r1101 + ] +] diff --git a/osmo-st-network/isup/ISUPTests.st b/osmo-st-network/isup/ISUPTests.st new file mode 100644 index 0000000..c3b849e --- /dev/null +++ b/osmo-st-network/isup/ISUPTests.st @@ -0,0 +1,78 @@ +" + (C) 2011-2012 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: ISUPGeneratedTest [ + + + + playWith: aField [ + aField name. + aField parameterValue. + aField octalLength. + self assert: aField isVarible ~= aField isFixed. + + aField isVarible ifTrue: [aField maxLength]. + ] + + testGeneration [ + ISUPMessage allSubclassesDo: [:class | + | struct | + struct := class tlvDescription. + struct fixed do: [:each | + self playWith: each]. + struct variable do: [:each | + self playWith: each]. + struct optional do: [:each | + self playWith: each]. + struct optionals do: [:each | + self playWith: each]. + + "same thing once more" + struct fieldsDo: [:type :field_class | + self playWith: field_class]. + ]. + ] + + 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. + + data := ISUPMessage encodeCollection: struct. + self assert: data asByteArray = decode. + ] + + testClassCount [ + self assert: ISUPMessage allSubclasses size = 46. + ] + + testSpecParmameterNameSmokeTest [ + MSGField allSubclassesDo: [:class | + class category = 'OsmoNetwork-ISUP' + ifTrue: [ + self + assert: class parameterName isString; + assert: class spec isString]]. + ] +] diff --git a/osmo-st-network/isup/generator/acm.txt b/osmo-st-network/isup/generator/acm.txt new file mode 100644 index 0000000..0a56970 --- /dev/null +++ b/osmo-st-network/isup/generator/acm.txt @@ -0,0 +1,27 @@ +Message type 2.1 F 1 +Backward call indicators 3.5 F 2 +Optional backward call indicators 3.37 O 3 +Call reference (national use) 3.8 O 7 +Cause indicators 3.12 O 4-? +User-to-user indicators 3.60 O 3 +User-to-user information 3.61 O 3-131 +Access transport 3.3 O 3-? +Generic notification indicator (Note 1) 3.25 O 3 +Transmission medium used 3.56 O 3 +Echo control information 3.19 O 3 +Access delivery information 3.2 O 3 +Redirection number (Note 2) 3.46 O 5-? +Parameter compatibility information 3.41 O 4-? +Call diversion information 3.6 O 3 +Network specific facility (national use) 3.36 O 4-? +Remote operations (national use) 3.48 O 8-? +Service activation 3.49 O 3-? +Redirection number restriction 3.47 O 3 +Conference treatment indicators 3.76 O 3-? +UID action indicators 3.78 O 3-? +Application transport parameter (Note 3) 3.82 O 5-? +CCNR possible indicator 3.83 O 3 +HTR information 3.89 O 4-? +Pivot routing backward information 3.95 O 3-? +Redirect status (national use) 3.98 O 3 +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/amn.txt b/osmo-st-network/isup/generator/amn.txt new file mode 100644 index 0000000..c1a202f --- /dev/null +++ b/osmo-st-network/isup/generator/amn.txt @@ -0,0 +1,27 @@ +Message type 2.1 F 1 +Backward call indicators 3.5 O 4 +Optional backward call indicators 3.37 O 3 +Call reference (national use) 3.8 O 7 +User-to-user indicators 3.60 O 3 +User-to-user information 3.61 O 3-131 +Connected number (Note 2) 3.16 O 4-? +Access transport 3.3 O 3-? +Access delivery information 3.2 O 3 +Generic notification indicator (Note 1) 3.25 O 3 +Parameter compatibility information 3.41 O 4-? +Backward GVNS 3.62 O 3-? +Call history information 3.7 O 4 +Generic number (Notes 1 and 2) 3.26 O 5-? +Transmission medium used 3.56 O 3 +Network specific facility (national use) 3.36 O 4-? +Remote operations (national use) 3.48 O 8-? +Redirection number (Note 2) 3.46 O 5-? +Service activation 3.49 O 3-? +Echo control information 3.19 O 3 +Redirection number restriction 3.47 O 3 +Display information 3.77 O 3-? +Conference treatment indicators 3.76 O 3-? +Application transport parameter (Note 3) 3.82 O 5-? +Pivot routing backward information 3.95 O 3-? +Redirect status (national use) 3.98 O 3 +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/apt.txt b/osmo-st-network/isup/generator/apt.txt new file mode 100644 index 0000000..24b473a --- /dev/null +++ b/osmo-st-network/isup/generator/apt.txt @@ -0,0 +1,6 @@ +# Application transport +Message type 2.1 F 1 +Message compatibility information 3.33 O 3-? +Parameter compatibility information 3.41 O 4-? +Application transport parameter (Note) 3.82 O 5-? +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/blo.txt b/osmo-st-network/isup/generator/blo.txt new file mode 100644 index 0000000..5d286a4 --- /dev/null +++ b/osmo-st-network/isup/generator/blo.txt @@ -0,0 +1 @@ +Message type 2.1 F 1 diff --git a/osmo-st-network/isup/generator/cfn.txt b/osmo-st-network/isup/generator/cfn.txt new file mode 100644 index 0000000..61ada9d --- /dev/null +++ b/osmo-st-network/isup/generator/cfn.txt @@ -0,0 +1,3 @@ +Message type 2.1 F 1 +Cause indicators 3.12 V 3-? +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/cgb.txt b/osmo-st-network/isup/generator/cgb.txt new file mode 100644 index 0000000..e9c6657 --- /dev/null +++ b/osmo-st-network/isup/generator/cgb.txt @@ -0,0 +1,3 @@ +Message type 2.1 F 1 +Circuit group supervision message type 3.13 F 1 +Range and status 3.43 V 3-34 diff --git a/osmo-st-network/isup/generator/con.txt b/osmo-st-network/isup/generator/con.txt new file mode 100644 index 0000000..356c531 --- /dev/null +++ b/osmo-st-network/isup/generator/con.txt @@ -0,0 +1,26 @@ +Message type 2.1 F 1 +Backward call indicators 3.5 F 2 +Optional backward call indicators 3.37 O 3 +Backward GVNS 3.62 O 3-? +Connected number (Note 2) 3.16 O 4-? +Call reference (national use) 3.8 O 7 +User-to-user indicators 3.60 O 3 +User-to-user information 3.61 O 3-131 +Access transport 3.3 O 3-? +Network specific facility (national use) 3.36 O 4-? +Generic notification indicator (Note 1) 3.25 O 3 +Remote operations (national use) 3.48 O 8-? +Transmission medium used 3.56 O 3 +Echo control information 3.19 O 3 +Access delivery information 3.2 O 3 +Call history information 3.7 O 4 +Parameter compatibility information 3.41 O 4-? +Service activation 3.49 O 3-? +Generic number (Notes 1 and 2) 3.26 O 5-? +Redirection number restriction 3.47 O 3 +Conference treatment indicators 3.76 O 3-? +Application transport parameter (Note 3) 3.82 O 5-? +HTR information 3.89 O 4-? +Pivot routing backward information 3.95 O 3-? +Redirect status (national use) 3.98 O 3 +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/cot.txt b/osmo-st-network/isup/generator/cot.txt new file mode 100644 index 0000000..37e9587 --- /dev/null +++ b/osmo-st-network/isup/generator/cot.txt @@ -0,0 +1,2 @@ +Message type 2.1 F 1 +Continuity indicators 3.18 F 1 diff --git a/osmo-st-network/isup/generator/cpg.txt b/osmo-st-network/isup/generator/cpg.txt new file mode 100644 index 0000000..163cf19 --- /dev/null +++ b/osmo-st-network/isup/generator/cpg.txt @@ -0,0 +1,32 @@ +Message type 2.1 F 1 +Event information 3.21 F 1 +Cause indicators 3.12 O 4-? +Call reference (national use) 3.8 O 7 +Backward call indicators 3.5 O 4 +Optional backward call indicators 3.37 O 3 +Access transport 3.3 O 3-? +User-to-user indicators 3.60 O 3 +Redirection number (Note 2) 3.46 O 5-? +User-to-user information 3.61 O 3-131 +Generic notification indicator (Note 1) 3.25 O 3 +Network specific facility (national use) 3.36 O 4-? +Remote operations (national use) 3.48 O 8-? +Transmission medium used 3.56 O 3 +Access delivery information 3.2 O 3 +Parameter compatibility information 3.41 O 4-? +Call diversion information 3.6 O 3 +Service activation 3.49 O 3-? +Redirection number restriction 3.47 O 3 +Call transfer number (Note 2) 3.64 O 4-? +Echo control information 3.19 O 3 +Connected number (Note 2) 3.16 O 4-? +Backward GVNS 3.62 O 3-? +Generic number (Notes 1 and 2) 3.26 O 5-? +Call history information 3.7 O 4 +Conference treatment indicators 3.76 O 3-? +UID action indicators 3.78 O 3-? +Application transport parameter (Note 3) 3.82 O 5-? +CCNR possible indicator 3.83 O 3 +Pivot routing backward information 3.95 O 3-? +Redirect status (national use) 3.98 O 3 +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/cqr.txt b/osmo-st-network/isup/generator/cqr.txt new file mode 100644 index 0000000..e321c54 --- /dev/null +++ b/osmo-st-network/isup/generator/cqr.txt @@ -0,0 +1,3 @@ +Message type 2.1 F 1 +Range 3.43b V 2 +Circuit state indicator (national use) 3.14 V 2-33 diff --git a/osmo-st-network/isup/generator/create_structs.st b/osmo-st-network/isup/generator/create_structs.st new file mode 100644 index 0000000..0178d0c --- /dev/null +++ b/osmo-st-network/isup/generator/create_structs.st @@ -0,0 +1,331 @@ +Object subclass: StructItem [ + | data | + StructItem class >> initWith: aData [ + ^ self new + data: aData; yourself + ] + + StructItem class >> makeCamelCase: aString [ + | res capital | + res := OrderedCollection new: aString size. + + capital := true. + 1 to: aString size do: [:pos | | item | + item := aString at: pos. + item = $' ifFalse: [ + + item = $ + ifTrue: [capital := true] + ifFalse: [ + capital + ifTrue: [res add: item asUppercase] + ifFalse: [res add: item]. + capital := false. + ]. + ]. + ]. + + ^ res asString + ] + + data: aData [ + data := aData reverse substrings: ' ' + ] + + isFixedLength [ ^ (self length indexOf: $-) = 0 ] + + minLength [ ^ (self length substrings: '-') at: 1 ] + maxLength [ ^ (self length substrings: '-') at: 2 ] + + isOptional [ ^ self type = 'O' ] + isVariable [ ^ self type = 'V' ] + isFixed [ ^ self type = 'F' ] + + appearsMultiple [ ^ ((self text indexOf: '(Note 3)' matchCase: false startingAt: 1) isNil not) or: [ + ((self text indexOf: '(Note 1)' matchCase: false startingAt: 1) isNil not)] ] + + name [ + | shorten | + "TODO: Run more things.... shorten.. replace Backward -> Backw and such" + shorten := self shortenText. + ^ ('ISUP' , (self class makeCamelCase: shorten)) ] + + className [ + | replaced makeUp | + makeUp := false. + replaced := OrderedCollection new. + self name do: [:each | + ((each = $/) or: [each = $-]) ifFalse: [ + makeUp ifTrue: [replaced add: each asUppercase] + ifFalse:[replaced add: each]. + makeUp := false] + ifTrue: [makeUp := true]. + ]. + + ^ replaced asString + ] + + param [ + ^ self className copyFrom: 5 + ] + + length [ ^ (data at: 1) reverse] + type [ ^ data at: 2 ] + ref [ ^ (data at: 3) reverse ] + text [ ^ (String join: (data copyFrom: 4) separatedBy: ' ') reverse ] + + shortenText [ + | text paren | + text := self text. + + (paren := text indexOf: $() > 0 ifTrue: [ + text := (text copyFrom: 1 to: paren - 1) trimSeparators. + ]. + + ^ text + ] + + commentName [ + | text replaced | + text := self shortenText. + replaced := OrderedCollection new. + text do: [:each | + replaced add: each. + each = $' ifTrue: [replaced add: $' ]. + ]. + + ^ replaced asString + ] +] + +Object subclass: StructCreator [ + | fields structs struct structName | + StructCreator class >> initWith: aFilename [ + ^ self new + file: (FileStream open: aFilename); + yourself + ] + + StructCreator class >> new [ + ^ super new + initialize + ] + + initialize [ + fields := Dictionary new. + structs := OrderedCollection new. + ] + + file: aFile [ + | out aStream | + struct := OrderedCollection new. + + structName := (aFile copyFrom: 1 to: (aFile indexOf: $.) - 1) asUppercase. + + aStream := FileStream open: aFile. + aStream linesDo: [:line | | def handle | + handle := (line indexOf: $#) = 0 and: [line size > 0]. + + handle ifTrue: [ + self parse: line. + ]. + ]. + struct add: ' yourself.'. + struct add: ' ]'. + struct add: ']'. + out := String join: struct separatedBy: Character nl asString. + + structs add: out. + ] + + parse: aLine [ + | def | + def := StructItem initWith: aLine. + [ + def isFixedLength + ifTrue: [self handleFixedLength: def] + ifFalse: [self handleVariableLength: def]. + + + self addStruct: def. + ] on: Exception do: [:e | e printNl. aLine printNl. e inspect]. + ] + + addType: aType struct: aStruct [ + fields at: aType ifPresent: [:other | + other = aStruct ifFalse: [ + ('Conflicting types of %1' % {aType}) printNl. + other printNl. + aStruct printNl. + ]. + ]. + + fields at: aType put: aStruct. + ] + + + handleFixedLength: aDef [ + "Some fields have conflicting types... E.g. Range and Status + appears sometimes only as range... without the status." + | len type tag_only | + aDef isFixed ifTrue: [len := aDef minLength]. + aDef isVariable ifTrue: [len := (Number readFrom: aDef minLength readStream) - 1]. + aDef isOptional ifTrue: [len := (Number readFrom: aDef minLength readStream) - 2]. + + len isNil ifTrue: [ + aDef isFixed printNl. + aDef isVariable printNl. + aDef isOptional printNl. + aDef minLength printNl. + ]. + + + tag_only := ''. + len <= 0 ifTrue: [ + len := 0. + tag_only := ' + %1 class >> lengthLength [ ^ 0 ] +' % {aDef className}. + ]. + + aDef className = 'ISUPMessageType' + ifTrue: [^self]. + + type := +'MSGFixedField subclass: %1 [ + + + + %1 class >> parameterName [ ^ ''%2'' ] + %1 class >> parameterValue [ ^ ISUPConstants par%3 ] + %1 class >> octalLength [ ^ %4 ] + %1 class >> spec [ ^ ''%5'' ]%6 +]' % {aDef className. aDef commentName. aDef param. len. aDef ref. tag_only.}. + + self addType: aDef ref struct: type. + ] + + handleVariableLength: aDef [ + | type minLen maxLen off | + + aDef isVariable ifTrue: [off := 1]. + aDef isOptional ifTrue: [off := 2]. + + minLen := (Number readFrom: aDef minLength readStream) - off. + maxLen := aDef maxLength. + maxLen = '?' ifTrue: [maxLen := nil.] + ifFalse: [maxLen := (Number readFrom: maxLen readStream) - off]. + + + type := +'MSGVariableField subclass: %1 [ + + + + %1 class >> parameterName [ ^ ''%2'' ] + %1 class >> parameterValue [ ^ ISUPConstants par%3 ] + %1 class >> octalLength [ ^ %4 ] + %1 class >> maxLength [ ^ %5 ] + %1 class >> spec [ ^ ''%6'' ] +]' % {aDef className. aDef commentName. aDef param. minLen. maxLen. aDef ref}. + + self addType: aDef ref struct: type. + ] + + addStruct: def [ + "Create boiler plate code" + struct isEmpty ifTrue: [ + struct add: ' +ISUPMessage subclass: ISUP%1 [ + + + + ISUP%1 class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msg%1)' % {structName. }. + ^ true + ]. + + def isFixed ifTrue: [ + struct add: ' addFixed: %1;' % {def className}. + ]. + def isVariable ifTrue: [ + struct add: ' addVariable: %1;' % {def className}. + ]. + def isOptional ifTrue: [ + def appearsMultiple + ifTrue: [struct add: ' addOptionals: %1;' % {def className}] + ifFalse: [struct add: ' addOptional: %1;' % {def className}] + ]. + ] + + structsDo: aBlock [ + structs do: aBlock. + ] + + typesDo: aBlock [ + fields do: aBlock. + ] +] + +Object subclass: SubclassCreator [ + | structs | + + + file: aName [ + | className baseName | + + className := (aName copyFrom: 6 to: (aName indexOf: $.) - 1) asUppercase. + baseName := ((FileStream open: aName) lines next copyFrom: 9) asUppercase. + + self structs add: ' +ISUP%1 subclass: ISUP%2 [ + + + + ISUP%2 class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msg%2; yourself + ] +]' % {baseName. className}. + ] + + + structsDo: aBlock [ + self structs do: aBlock. + ] + + structs [ + ^ structs ifNil: [structs := OrderedCollection new] + ] +] + +Eval [ + | struct outp subs | + same := #('same_bla.txt' 'same_ccr.txt' 'same_cgba.txt' 'same_cgua.txt' + 'same_cgu.txt' 'same_far.txt' 'same_gra.txt' 'same_lpa.txt' + 'same_olm.txt' 'same_rsc.txt' 'same_sus.txt' 'same_uba.txt' + 'same_ubl.txt' 'same_ucic.txt' 'same_upa.txt'). + files := #('acm.txt' 'amn.txt' 'apt.txt' 'blo.txt' 'cfn.txt' 'cgb.txt' 'con.txt' + 'cot.txt' 'cpg.txt' 'cqr.txt' 'faa.txt' 'fac.txt' 'fot.txt' 'frj.txt' + 'gra.txt' 'grs.txt' 'iam.txt' 'idr.txt' 'ids.txt' 'inf.txt' 'inr.txt' + 'lpr.txt' 'nrm.txt' 'pri.txt' 'rel.txt' 'res.txt' 'rlc.txt' + 'sam.txt' 'san.txt' 'seg.txt' 'upt.txt' 'usr.txt'). + struct := StructCreator new. + + files do: [:each | struct file: each. ]. + + outp := FileStream open: 'isup_generated.st' mode: 'w'. + outp nextPutAll: '"Types for ISUP"'. + outp nextPut: Character nl. + struct typesDo: [:each | outp nextPutAll: each. outp nextPut: Character nl. outp nextPut: Character nl.]. + + outp nextPutAll: '"MSGs for ISUP"'. + struct structsDo: [:struct | outp nextPutAll: struct. outp nextPut: Character nl. outp nextPut: Character nl]. + + subs := SubclassCreator new. + same do: [:each | subs file: each. ]. + subs structsDo: [:struct | outp nextPutAll: struct. outp nextPut: Character nl; nextPut: Character nl.] +] diff --git a/osmo-st-network/isup/generator/faa.txt b/osmo-st-network/isup/generator/faa.txt new file mode 100644 index 0000000..3744bf7 --- /dev/null +++ b/osmo-st-network/isup/generator/faa.txt @@ -0,0 +1,7 @@ +Message type 2.1 F 1 +Facility indicator 3.22 F 1 +User-to-user indicators 3.60 O 3 +Call reference (national use) 3.8 O 7 +Connection request 3.17 O 7-9 +Parameter compatibility information 3.41 O 4-? +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/fac.txt b/osmo-st-network/isup/generator/fac.txt new file mode 100644 index 0000000..ad7538f --- /dev/null +++ b/osmo-st-network/isup/generator/fac.txt @@ -0,0 +1,16 @@ +#Facility +Message type 2.1 F 1 +Message compatibility information 3.33 O 3-? +Parameter compatibility information 3.41 O 4-? +Remote operations (national use) 3.48 O 8-? +Service activation 3.49 O 3-? +Call transfer number (Note) 3.64 O 4-? +Access transport 3.3 O 3-? +Generic notification indicator 3.25 O 3 +Redirection number 3.46 O 5-? +Pivot routing indicators 3.85 O 3 +Pivot status (national use) 3.92 O 3 +Pivot counter 3.93 O 3 +Pivot routing backward information 3.95 O 3-? +Redirect status (national use) 3.98 O 3 +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/fot.txt b/osmo-st-network/isup/generator/fot.txt new file mode 100644 index 0000000..aa39d8f --- /dev/null +++ b/osmo-st-network/isup/generator/fot.txt @@ -0,0 +1,3 @@ +Message type 2.1 F 1 +Call reference (national use) 3.8 O 7 +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/frj.txt b/osmo-st-network/isup/generator/frj.txt new file mode 100644 index 0000000..b2a15dd --- /dev/null +++ b/osmo-st-network/isup/generator/frj.txt @@ -0,0 +1,5 @@ +Message type 2.1 F 1 +Facility indicator 3.22 F 1 +Cause indicators 3.12 V 3-? +User-to-user indicators 3.60 O 3 +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/gra.txt b/osmo-st-network/isup/generator/gra.txt new file mode 100644 index 0000000..2c0f4d7 --- /dev/null +++ b/osmo-st-network/isup/generator/gra.txt @@ -0,0 +1,2 @@ +Message type 2.1 F 1 +Range and status 3.43 V 3-34 diff --git a/osmo-st-network/isup/generator/grs.txt b/osmo-st-network/isup/generator/grs.txt new file mode 100644 index 0000000..8fb22f7 --- /dev/null +++ b/osmo-st-network/isup/generator/grs.txt @@ -0,0 +1,2 @@ +Message type 2.1 F 1 +Range 3.43b V 2 diff --git a/osmo-st-network/isup/generator/iam.txt b/osmo-st-network/isup/generator/iam.txt new file mode 100644 index 0000000..52ca271 --- /dev/null +++ b/osmo-st-network/isup/generator/iam.txt @@ -0,0 +1,64 @@ +Message type 2.1 F 1 +Nature of connection indicators 3.35 F 1 +Forward call indicators 3.23 F 2 +Calling party's category 3.11 F 1 +Transmission medium requirement 3.54 F 1 +Called party number (Note 2) 3.9 V 4-? +Transit network selection (national use) 3.53 O 4-? +Call reference (national use) 3.8 O 7 +Calling party number (Note 2) 3.10 O 4-? +Optional forward call indicators 3.38 O 3 +Redirecting number (Note 2) 3.44 O 4-? +Redirection information 3.45 O 3-4 +Closed user group interlock code 3.15 O 6 +Connection request 3.17 O 7-9 +Original called number (Note 2) 3.39 O 4-? +User-to-user information 3.61 O 3-131 +Access transport 3.3 O 3-? +User service information 3.57 O 4-13 +User-to-user indicators 3.60 O 3 +Generic number (Notes 1 and 2) 3.26 O 5-? +Propagation delay counter 3.42 O 4 +User service information prime 3.58 O 4-13 +Network specific facility (national use) 3.36 O 4-? +Generic digits (national use) (Note 1) 3.24 O 4-? +Origination ISC point code 3.40 O 4 +User teleservice information 3.59 O 4-5 +Remote operations (national use) 3.48 O 8-? +Parameter compatibility information 3.41 O 4-? +Generic notification indicator (Note 1) 3.25 O 3 +Service activation 3.49 O 3-? +Generic reference (reserved ) 3.27 O 5-? +MLPP precedence 3.34 O 8 +Transmission medium requirement prime 3.55 O 3 +Location number (Note 2) 3.30 O 4-? +Forward GVNS 3.66 O 5-26 +CCSS 3.63 O 3-? +Network management controls 3.68 O 3-? +Circuit assignment map 3.69 O 6-7 +Correlation id 3.70 O 3-? +Call diversion treatment indicators 3.72 O 3-? +Called IN number (Note 2) 3.73 O 4-? +Call offering treatment indicators 3.74 O 3-? +Conference treatment indicators 3.76 O 3-? +SCF id 3.71 O 3-? +UID capability indicators 3.79 O 3-? +Echo control information 3.19 O 3 +Hop counter 3.80 O 3 +Collect call request 3.81 O 3 +Application transport parameter (Note 3) 3.82 O 5-? +Pivot capability 3.84 O 3 +Called directory number (national use) 3.86 O 5-? +Original called IN number 3.87 O 4-? +Calling geodetic location 3.88 O 3-? +Network routing number (national use) 3.90 O 4-? +QoR capability (network option) 3.91 O 3 +Pivot counter 3.93 O 3 +Pivot routing forward information 3.94 O 3-? +Redirect capability (national use) 3.96 O 3 +Redirect counter (national use) 3.97 O 3 +Redirect status 3.98 O 3 +Redirect forward information (national use) 3.99 O 3-? +Number portability forward information (network option) 3.101 O 1-? +End of optional parameters 3.20 O 1 + diff --git a/osmo-st-network/isup/generator/idr.txt b/osmo-st-network/isup/generator/idr.txt new file mode 100644 index 0000000..3f65729 --- /dev/null +++ b/osmo-st-network/isup/generator/idr.txt @@ -0,0 +1,6 @@ +# Identification request +Message type 2.1 F 1 +MCID request indicators 3.31 O 3 +Message compatibility information 3.33 O 3-? +Parameter compatibility information 3.41 O 4-? +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/ids.txt b/osmo-st-network/isup/generator/ids.txt new file mode 100644 index 0000000..3b83840 --- /dev/null +++ b/osmo-st-network/isup/generator/ids.txt @@ -0,0 +1,10 @@ +# Identification response +Message type 2.1 F 1 +MCID response indicators 3.32 O 3 +Message compatibility information 3.33 O 3-? +Parameter compatibility information 3.41 O 4-? +Calling party number (Note 2) 3.10 O 4-? +Access transport 3.3 O 3-? +Generic number (Notes 1 and 2) 3.26 O 5-? +Charged party identification (national use) 3.75 O 3-? +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/inf.txt b/osmo-st-network/isup/generator/inf.txt new file mode 100644 index 0000000..2c70731 --- /dev/null +++ b/osmo-st-network/isup/generator/inf.txt @@ -0,0 +1,9 @@ +Message type 2.1 F 1 +Information indicators (national use) 3.28 F 2 +Calling party's category 3.11 O 3 +Calling party number (Note) 3.10 O 4-? +Call reference (national use) 3.8 O 7 +Connection request 3.17 O 7-9 +Parameter compatibility information 3.41 O 4-? +Network specific facility 3.36 O 4-? +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/inr.txt b/osmo-st-network/isup/generator/inr.txt new file mode 100644 index 0000000..479b611 --- /dev/null +++ b/osmo-st-network/isup/generator/inr.txt @@ -0,0 +1,6 @@ +Message type 2.1 F 1 +Information request indicators (national use) 3.29 F 2 +Call reference (national use) 3.8 O 7 +Network specific facility 3.36 O 4-? +Parameter compatibility information 3.41 O 4-? +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/lpr.txt b/osmo-st-network/isup/generator/lpr.txt new file mode 100644 index 0000000..6bf7bdb --- /dev/null +++ b/osmo-st-network/isup/generator/lpr.txt @@ -0,0 +1,7 @@ +# Loop prevention +Message type 2.1 F 1 +Message compatibility information 3.33 O 3-? +Parameter compatibility information 3.41 O 4-? +Call transfer reference 3.65 O 3 +Loop prevention indicators 3.67 O 3 +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/nrm.txt b/osmo-st-network/isup/generator/nrm.txt new file mode 100644 index 0000000..d0dc5a1 --- /dev/null +++ b/osmo-st-network/isup/generator/nrm.txt @@ -0,0 +1,6 @@ +#Network Resource management +Message type 2.1 F 1 +Message compatibility information 3.33 O 3-? +Parameter compatibility information 3.41 O 4-? +Echo control information 3.19 O 3 +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/pri.txt b/osmo-st-network/isup/generator/pri.txt new file mode 100644 index 0000000..ac6dd13 --- /dev/null +++ b/osmo-st-network/isup/generator/pri.txt @@ -0,0 +1,8 @@ +#Pre-Release information +Message type 2.1 F 1 +Message compatibility information 3.33 O 3-? +Parameter compatibility information 3.41 O 4-? +Optional forward call indicators (Note 1) 3.38 O 3 +Optional backward call indicators (Note 1) 3.37 O 3 +Application transport parameter (Note 2) 3.82 O 5-? +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/rel.txt b/osmo-st-network/isup/generator/rel.txt new file mode 100644 index 0000000..9fe398b --- /dev/null +++ b/osmo-st-network/isup/generator/rel.txt @@ -0,0 +1,18 @@ +Message type 2.1 F 1 +Cause indicators 3.12 V 3-? +Redirection information (national use) 3.45 O 3-4 +Redirection number (national use) (Note) 3.46 O 5-? +Access transport 3.3 O 3-? +Signalling point code (national use) 3.50 O 4 +User-to-user information 3.61 O 3-131 +Automatic congestion level 3.4 O 3 +Network specific facility (national use) 3.36 O 4-? +Access delivery information 3.2 O 3 +Parameter compatibility information 3.41 O 4-? +User-to-user indicators 3.60 O 3 +Display information 3.77 O 3-? +Remote operations (national use) 3.48 O 8-? +HTR information 3.89 O 4-? +Redirect counter (national use) 3.97 O 3 +Redirect backward information (national use) 3.100 O 3-? +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/res.txt b/osmo-st-network/isup/generator/res.txt new file mode 100644 index 0000000..03ec43f --- /dev/null +++ b/osmo-st-network/isup/generator/res.txt @@ -0,0 +1,4 @@ +Message type 2.1 F 1 +Suspend/resume indicators 3.52 F 1 +Call reference (national use) 3.8 O 7 +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/rlc.txt b/osmo-st-network/isup/generator/rlc.txt new file mode 100644 index 0000000..cf8f11c --- /dev/null +++ b/osmo-st-network/isup/generator/rlc.txt @@ -0,0 +1,3 @@ +Message type 2.1 F 1 +Cause indicators 3.12 O 4-? +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/sam.txt b/osmo-st-network/isup/generator/sam.txt new file mode 100644 index 0000000..3c52de5 --- /dev/null +++ b/osmo-st-network/isup/generator/sam.txt @@ -0,0 +1,3 @@ +Message type 2.1 F 1 +Subsequent number (Note 2) 3.51 V 3-? +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/same_bla.txt b/osmo-st-network/isup/generator/same_bla.txt new file mode 100644 index 0000000..3be0310 --- /dev/null +++ b/osmo-st-network/isup/generator/same_bla.txt @@ -0,0 +1 @@ +sameas: blo diff --git a/osmo-st-network/isup/generator/same_ccr.txt b/osmo-st-network/isup/generator/same_ccr.txt new file mode 100644 index 0000000..3be0310 --- /dev/null +++ b/osmo-st-network/isup/generator/same_ccr.txt @@ -0,0 +1 @@ +sameas: blo diff --git a/osmo-st-network/isup/generator/same_cgba.txt b/osmo-st-network/isup/generator/same_cgba.txt new file mode 100644 index 0000000..bd5d2d8 --- /dev/null +++ b/osmo-st-network/isup/generator/same_cgba.txt @@ -0,0 +1 @@ +sameas: cgb diff --git a/osmo-st-network/isup/generator/same_cgu.txt b/osmo-st-network/isup/generator/same_cgu.txt new file mode 100644 index 0000000..bd5d2d8 --- /dev/null +++ b/osmo-st-network/isup/generator/same_cgu.txt @@ -0,0 +1 @@ +sameas: cgb diff --git a/osmo-st-network/isup/generator/same_cgua.txt b/osmo-st-network/isup/generator/same_cgua.txt new file mode 100644 index 0000000..bd5d2d8 --- /dev/null +++ b/osmo-st-network/isup/generator/same_cgua.txt @@ -0,0 +1 @@ +sameas: cgb diff --git a/osmo-st-network/isup/generator/same_far.txt b/osmo-st-network/isup/generator/same_far.txt new file mode 100644 index 0000000..303e871 --- /dev/null +++ b/osmo-st-network/isup/generator/same_far.txt @@ -0,0 +1 @@ +sameas: faa diff --git a/osmo-st-network/isup/generator/same_gra.txt b/osmo-st-network/isup/generator/same_gra.txt new file mode 100644 index 0000000..dc43376 --- /dev/null +++ b/osmo-st-network/isup/generator/same_gra.txt @@ -0,0 +1 @@ +sameas: grs diff --git a/osmo-st-network/isup/generator/same_lpa.txt b/osmo-st-network/isup/generator/same_lpa.txt new file mode 100644 index 0000000..3be0310 --- /dev/null +++ b/osmo-st-network/isup/generator/same_lpa.txt @@ -0,0 +1 @@ +sameas: blo diff --git a/osmo-st-network/isup/generator/same_olm.txt b/osmo-st-network/isup/generator/same_olm.txt new file mode 100644 index 0000000..3be0310 --- /dev/null +++ b/osmo-st-network/isup/generator/same_olm.txt @@ -0,0 +1 @@ +sameas: blo diff --git a/osmo-st-network/isup/generator/same_rsc.txt b/osmo-st-network/isup/generator/same_rsc.txt new file mode 100644 index 0000000..3be0310 --- /dev/null +++ b/osmo-st-network/isup/generator/same_rsc.txt @@ -0,0 +1 @@ +sameas: blo diff --git a/osmo-st-network/isup/generator/same_sus.txt b/osmo-st-network/isup/generator/same_sus.txt new file mode 100644 index 0000000..96982e8 --- /dev/null +++ b/osmo-st-network/isup/generator/same_sus.txt @@ -0,0 +1 @@ +sameas: res diff --git a/osmo-st-network/isup/generator/same_uba.txt b/osmo-st-network/isup/generator/same_uba.txt new file mode 100644 index 0000000..3be0310 --- /dev/null +++ b/osmo-st-network/isup/generator/same_uba.txt @@ -0,0 +1 @@ +sameas: blo diff --git a/osmo-st-network/isup/generator/same_ubl.txt b/osmo-st-network/isup/generator/same_ubl.txt new file mode 100644 index 0000000..3be0310 --- /dev/null +++ b/osmo-st-network/isup/generator/same_ubl.txt @@ -0,0 +1 @@ +sameas: blo diff --git a/osmo-st-network/isup/generator/same_ucic.txt b/osmo-st-network/isup/generator/same_ucic.txt new file mode 100644 index 0000000..3be0310 --- /dev/null +++ b/osmo-st-network/isup/generator/same_ucic.txt @@ -0,0 +1 @@ +sameas: blo diff --git a/osmo-st-network/isup/generator/same_upa.txt b/osmo-st-network/isup/generator/same_upa.txt new file mode 100644 index 0000000..c401601 --- /dev/null +++ b/osmo-st-network/isup/generator/same_upa.txt @@ -0,0 +1 @@ +sameas: upt diff --git a/osmo-st-network/isup/generator/san.txt b/osmo-st-network/isup/generator/san.txt new file mode 100644 index 0000000..c8ae836 --- /dev/null +++ b/osmo-st-network/isup/generator/san.txt @@ -0,0 +1,6 @@ +#Subsequent directory number +Message type 2.1 F 1 +Subsequent number 3.51 O 4-? +Message compatibility information 3.33 O 3-? +End of optional parameters 3.20 O 1 + diff --git a/osmo-st-network/isup/generator/seg.txt b/osmo-st-network/isup/generator/seg.txt new file mode 100644 index 0000000..9b77788 --- /dev/null +++ b/osmo-st-network/isup/generator/seg.txt @@ -0,0 +1,9 @@ +# Segmentation +Message type 2.1 F 1 +Access transport 3.3 O 3-? +User-to-user information 3.61 O 3-131 +Message compatibility information 3.33 O 3-? +Generic digits (national use) (Note 1) 3.24 O 4-? +Generic notification indicator (Note 1) 3.25 O 3 +Generic number (Notes 1 and 2) 3.26 O 5-? +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/upt.txt b/osmo-st-network/isup/generator/upt.txt new file mode 100644 index 0000000..e6c3853 --- /dev/null +++ b/osmo-st-network/isup/generator/upt.txt @@ -0,0 +1,4 @@ +# User part test and User part available +Message type 2.1 F 1 +Parameter compatibility information 3.41 O 4-? +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/generator/usr.txt b/osmo-st-network/isup/generator/usr.txt new file mode 100644 index 0000000..913496e --- /dev/null +++ b/osmo-st-network/isup/generator/usr.txt @@ -0,0 +1,4 @@ +Message type 2.1 F 1 +User-to-user information 3.61 V 2-130 +Access transport 3.3 O 3-? +End of optional parameters 3.20 O 1 diff --git a/osmo-st-network/isup/isup_generated.st b/osmo-st-network/isup/isup_generated.st new file mode 100644 index 0000000..219b19b --- /dev/null +++ b/osmo-st-network/isup/isup_generated.st @@ -0,0 +1,1919 @@ +"Types for ISUP" +MSGFixedField subclass: ISUPEndOfOptionalParameters [ + + + + ISUPEndOfOptionalParameters class >> parameterName [ ^ 'End of optional parameters' ] + ISUPEndOfOptionalParameters class >> parameterValue [ ^ ISUPConstants parEndOfOptionalParameters ] + ISUPEndOfOptionalParameters class >> octalLength [ ^ 0 ] + ISUPEndOfOptionalParameters class >> spec [ ^ '3.20' ] + ISUPEndOfOptionalParameters class >> lengthLength [ ^ 0 ] + +] + +MSGVariableField subclass: ISUPCorrelationId [ + + + + ISUPCorrelationId class >> parameterName [ ^ 'Correlation id' ] + ISUPCorrelationId class >> parameterValue [ ^ ISUPConstants parCorrelationId ] + ISUPCorrelationId class >> octalLength [ ^ 1 ] + ISUPCorrelationId class >> maxLength [ ^ nil ] + ISUPCorrelationId class >> spec [ ^ '3.70' ] +] + +MSGFixedField subclass: ISUPCallingPartysCategory [ + + + + ISUPCallingPartysCategory class >> parameterName [ ^ 'Calling party''s category' ] + ISUPCallingPartysCategory class >> parameterValue [ ^ ISUPConstants parCallingPartysCategory ] + ISUPCallingPartysCategory class >> octalLength [ ^ 1 ] + ISUPCallingPartysCategory class >> spec [ ^ '3.11' ] +] + +MSGFixedField subclass: ISUPPivotStatus [ + + + + ISUPPivotStatus class >> parameterName [ ^ 'Pivot status' ] + ISUPPivotStatus class >> parameterValue [ ^ ISUPConstants parPivotStatus ] + ISUPPivotStatus class >> octalLength [ ^ 1 ] + ISUPPivotStatus class >> spec [ ^ '3.92' ] +] + +MSGFixedField subclass: ISUPCollectCallRequest [ + + + + ISUPCollectCallRequest class >> parameterName [ ^ 'Collect call request' ] + ISUPCollectCallRequest class >> parameterValue [ ^ ISUPConstants parCollectCallRequest ] + ISUPCollectCallRequest class >> octalLength [ ^ 1 ] + ISUPCollectCallRequest class >> spec [ ^ '3.81' ] +] + +MSGVariableField subclass: ISUPSubsequentNumber [ + + + + ISUPSubsequentNumber class >> parameterName [ ^ 'Subsequent number' ] + ISUPSubsequentNumber class >> parameterValue [ ^ ISUPConstants parSubsequentNumber ] + ISUPSubsequentNumber class >> octalLength [ ^ 2 ] + ISUPSubsequentNumber class >> maxLength [ ^ nil ] + ISUPSubsequentNumber class >> spec [ ^ '3.51' ] +] + +MSGFixedField subclass: ISUPNatureOfConnectionIndicators [ + + + + ISUPNatureOfConnectionIndicators class >> parameterName [ ^ 'Nature of connection indicators' ] + ISUPNatureOfConnectionIndicators class >> parameterValue [ ^ ISUPConstants parNatureOfConnectionIndicators ] + ISUPNatureOfConnectionIndicators class >> octalLength [ ^ 1 ] + ISUPNatureOfConnectionIndicators class >> spec [ ^ '3.35' ] +] + +MSGFixedField subclass: ISUPPropagationDelayCounter [ + + + + ISUPPropagationDelayCounter class >> parameterName [ ^ 'Propagation delay counter' ] + ISUPPropagationDelayCounter class >> parameterValue [ ^ ISUPConstants parPropagationDelayCounter ] + ISUPPropagationDelayCounter class >> octalLength [ ^ 2 ] + ISUPPropagationDelayCounter class >> spec [ ^ '3.42' ] +] + +MSGFixedField subclass: ISUPRedirectCounter [ + + + + ISUPRedirectCounter class >> parameterName [ ^ 'Redirect counter' ] + ISUPRedirectCounter class >> parameterValue [ ^ ISUPConstants parRedirectCounter ] + ISUPRedirectCounter class >> octalLength [ ^ 1 ] + ISUPRedirectCounter class >> spec [ ^ '3.97' ] +] + +MSGFixedField subclass: ISUPForwardCallIndicators [ + + + + ISUPForwardCallIndicators class >> parameterName [ ^ 'Forward call indicators' ] + ISUPForwardCallIndicators class >> parameterValue [ ^ ISUPConstants parForwardCallIndicators ] + ISUPForwardCallIndicators class >> octalLength [ ^ 2 ] + ISUPForwardCallIndicators class >> spec [ ^ '3.23' ] +] + +MSGVariableField subclass: ISUPBackwardGVNS [ + + + + ISUPBackwardGVNS class >> parameterName [ ^ 'Backward GVNS' ] + ISUPBackwardGVNS class >> parameterValue [ ^ ISUPConstants parBackwardGVNS ] + ISUPBackwardGVNS class >> octalLength [ ^ 1 ] + ISUPBackwardGVNS class >> maxLength [ ^ nil ] + ISUPBackwardGVNS class >> spec [ ^ '3.62' ] +] + +MSGFixedField subclass: ISUPOptionalForwardCallIndicators [ + + + + ISUPOptionalForwardCallIndicators class >> parameterName [ ^ 'Optional forward call indicators' ] + ISUPOptionalForwardCallIndicators class >> parameterValue [ ^ ISUPConstants parOptionalForwardCallIndicators ] + ISUPOptionalForwardCallIndicators class >> octalLength [ ^ 1 ] + ISUPOptionalForwardCallIndicators class >> spec [ ^ '3.38' ] +] + +MSGVariableField subclass: ISUPUserServiceInformation [ + + + + ISUPUserServiceInformation class >> parameterName [ ^ 'User service information' ] + ISUPUserServiceInformation class >> parameterValue [ ^ ISUPConstants parUserServiceInformation ] + ISUPUserServiceInformation class >> octalLength [ ^ 2 ] + ISUPUserServiceInformation class >> maxLength [ ^ 11 ] + ISUPUserServiceInformation class >> spec [ ^ '3.57' ] +] + +MSGVariableField subclass: ISUPNetworkManagementControls [ + + + + ISUPNetworkManagementControls class >> parameterName [ ^ 'Network management controls' ] + ISUPNetworkManagementControls class >> parameterValue [ ^ ISUPConstants parNetworkManagementControls ] + ISUPNetworkManagementControls class >> octalLength [ ^ 1 ] + ISUPNetworkManagementControls class >> maxLength [ ^ nil ] + ISUPNetworkManagementControls class >> spec [ ^ '3.68' ] +] + +MSGVariableField subclass: ISUPCalledINNumber [ + + + + ISUPCalledINNumber class >> parameterName [ ^ 'Called IN number' ] + ISUPCalledINNumber class >> parameterValue [ ^ ISUPConstants parCalledINNumber ] + ISUPCalledINNumber class >> octalLength [ ^ 2 ] + ISUPCalledINNumber class >> maxLength [ ^ nil ] + ISUPCalledINNumber class >> spec [ ^ '3.73' ] +] + +MSGVariableField subclass: ISUPCauseIndicators [ + + + + ISUPCauseIndicators class >> parameterName [ ^ 'Cause indicators' ] + ISUPCauseIndicators class >> parameterValue [ ^ ISUPConstants parCauseIndicators ] + ISUPCauseIndicators class >> octalLength [ ^ 2 ] + ISUPCauseIndicators class >> maxLength [ ^ nil ] + ISUPCauseIndicators class >> spec [ ^ '3.12' ] +] + +MSGFixedField subclass: ISUPQoRCapability [ + + + + ISUPQoRCapability class >> parameterName [ ^ 'QoR capability' ] + ISUPQoRCapability class >> parameterValue [ ^ ISUPConstants parQoRCapability ] + ISUPQoRCapability class >> octalLength [ ^ 1 ] + ISUPQoRCapability class >> spec [ ^ '3.91' ] +] + +MSGFixedField subclass: ISUPCallTransferReference [ + + + + ISUPCallTransferReference class >> parameterName [ ^ 'Call transfer reference' ] + ISUPCallTransferReference class >> parameterValue [ ^ ISUPConstants parCallTransferReference ] + ISUPCallTransferReference class >> octalLength [ ^ 1 ] + ISUPCallTransferReference class >> spec [ ^ '3.65' ] +] + +MSGFixedField subclass: ISUPAutomaticCongestionLevel [ + + + + ISUPAutomaticCongestionLevel class >> parameterName [ ^ 'Automatic congestion level' ] + ISUPAutomaticCongestionLevel class >> parameterValue [ ^ ISUPConstants parAutomaticCongestionLevel ] + ISUPAutomaticCongestionLevel class >> octalLength [ ^ 1 ] + ISUPAutomaticCongestionLevel class >> spec [ ^ '3.4' ] +] + +MSGVariableField subclass: ISUPRemoteOperations [ + + + + ISUPRemoteOperations class >> parameterName [ ^ 'Remote operations' ] + ISUPRemoteOperations class >> parameterValue [ ^ ISUPConstants parRemoteOperations ] + ISUPRemoteOperations class >> octalLength [ ^ 6 ] + ISUPRemoteOperations class >> maxLength [ ^ nil ] + ISUPRemoteOperations class >> spec [ ^ '3.48' ] +] + +MSGFixedField subclass: ISUPSuspendResumeIndicators [ + + + + ISUPSuspendResumeIndicators class >> parameterName [ ^ 'Suspend/resume indicators' ] + ISUPSuspendResumeIndicators class >> parameterValue [ ^ ISUPConstants parSuspendResumeIndicators ] + ISUPSuspendResumeIndicators class >> octalLength [ ^ 1 ] + ISUPSuspendResumeIndicators class >> spec [ ^ '3.52' ] +] + +MSGVariableField subclass: ISUPRedirectionInformation [ + + + + ISUPRedirectionInformation class >> parameterName [ ^ 'Redirection information' ] + ISUPRedirectionInformation class >> parameterValue [ ^ ISUPConstants parRedirectionInformation ] + ISUPRedirectionInformation class >> octalLength [ ^ 1 ] + ISUPRedirectionInformation class >> maxLength [ ^ 2 ] + ISUPRedirectionInformation class >> spec [ ^ '3.45' ] +] + +MSGVariableField subclass: ISUPConferenceTreatmentIndicators [ + + + + ISUPConferenceTreatmentIndicators class >> parameterName [ ^ 'Conference treatment indicators' ] + ISUPConferenceTreatmentIndicators class >> parameterValue [ ^ ISUPConstants parConferenceTreatmentIndicators ] + ISUPConferenceTreatmentIndicators class >> octalLength [ ^ 1 ] + ISUPConferenceTreatmentIndicators class >> maxLength [ ^ nil ] + ISUPConferenceTreatmentIndicators class >> spec [ ^ '3.76' ] +] + +MSGVariableField subclass: ISUPConnectionRequest [ + + + + ISUPConnectionRequest class >> parameterName [ ^ 'Connection request' ] + ISUPConnectionRequest class >> parameterValue [ ^ ISUPConstants parConnectionRequest ] + ISUPConnectionRequest class >> octalLength [ ^ 5 ] + ISUPConnectionRequest class >> maxLength [ ^ 7 ] + ISUPConnectionRequest class >> spec [ ^ '3.17' ] +] + +MSGFixedField subclass: ISUPCallHistoryInformation [ + + + + ISUPCallHistoryInformation class >> parameterName [ ^ 'Call history information' ] + ISUPCallHistoryInformation class >> parameterValue [ ^ ISUPConstants parCallHistoryInformation ] + ISUPCallHistoryInformation class >> octalLength [ ^ 2 ] + ISUPCallHistoryInformation class >> spec [ ^ '3.7' ] +] + +MSGVariableField subclass: ISUPCalledDirectoryNumber [ + + + + ISUPCalledDirectoryNumber class >> parameterName [ ^ 'Called directory number' ] + ISUPCalledDirectoryNumber class >> parameterValue [ ^ ISUPConstants parCalledDirectoryNumber ] + ISUPCalledDirectoryNumber class >> octalLength [ ^ 3 ] + ISUPCalledDirectoryNumber class >> maxLength [ ^ nil ] + ISUPCalledDirectoryNumber class >> spec [ ^ '3.86' ] +] + +MSGFixedField subclass: ISUPRedirectCapability [ + + + + ISUPRedirectCapability class >> parameterName [ ^ 'Redirect capability' ] + ISUPRedirectCapability class >> parameterValue [ ^ ISUPConstants parRedirectCapability ] + ISUPRedirectCapability class >> octalLength [ ^ 1 ] + ISUPRedirectCapability class >> spec [ ^ '3.96' ] +] + +MSGVariableField subclass: ISUPRedirectBackwardInformation [ + + + + ISUPRedirectBackwardInformation class >> parameterName [ ^ 'Redirect backward information' ] + ISUPRedirectBackwardInformation class >> parameterValue [ ^ ISUPConstants parRedirectBackwardInformation ] + ISUPRedirectBackwardInformation class >> octalLength [ ^ 1 ] + ISUPRedirectBackwardInformation class >> maxLength [ ^ nil ] + ISUPRedirectBackwardInformation class >> spec [ ^ '3.100' ] +] + +MSGVariableField subclass: ISUPGenericDigits [ + + + + ISUPGenericDigits class >> parameterName [ ^ 'Generic digits' ] + ISUPGenericDigits class >> parameterValue [ ^ ISUPConstants parGenericDigits ] + ISUPGenericDigits class >> octalLength [ ^ 2 ] + ISUPGenericDigits class >> maxLength [ ^ nil ] + ISUPGenericDigits class >> spec [ ^ '3.24' ] +] + +MSGVariableField subclass: ISUPOriginalCalledNumber [ + + + + ISUPOriginalCalledNumber class >> parameterName [ ^ 'Original called number' ] + ISUPOriginalCalledNumber class >> parameterValue [ ^ ISUPConstants parOriginalCalledNumber ] + ISUPOriginalCalledNumber class >> octalLength [ ^ 2 ] + ISUPOriginalCalledNumber class >> maxLength [ ^ nil ] + ISUPOriginalCalledNumber class >> spec [ ^ '3.39' ] +] + +MSGVariableField subclass: ISUPRedirectionNumber [ + + + + ISUPRedirectionNumber class >> parameterName [ ^ 'Redirection number' ] + ISUPRedirectionNumber class >> parameterValue [ ^ ISUPConstants parRedirectionNumber ] + ISUPRedirectionNumber class >> octalLength [ ^ 3 ] + ISUPRedirectionNumber class >> maxLength [ ^ nil ] + ISUPRedirectionNumber class >> spec [ ^ '3.46' ] +] + +MSGFixedField subclass: ISUPPivotRoutingIndicators [ + + + + ISUPPivotRoutingIndicators class >> parameterName [ ^ 'Pivot routing indicators' ] + ISUPPivotRoutingIndicators class >> parameterValue [ ^ ISUPConstants parPivotRoutingIndicators ] + ISUPPivotRoutingIndicators class >> octalLength [ ^ 1 ] + ISUPPivotRoutingIndicators class >> spec [ ^ '3.85' ] +] + +MSGVariableField subclass: ISUPCallingGeodeticLocation [ + + + + ISUPCallingGeodeticLocation class >> parameterName [ ^ 'Calling geodetic location' ] + ISUPCallingGeodeticLocation class >> parameterValue [ ^ ISUPConstants parCallingGeodeticLocation ] + ISUPCallingGeodeticLocation class >> octalLength [ ^ 1 ] + ISUPCallingGeodeticLocation class >> maxLength [ ^ nil ] + ISUPCallingGeodeticLocation class >> spec [ ^ '3.88' ] +] + +MSGVariableField subclass: ISUPSCFId [ + + + + ISUPSCFId class >> parameterName [ ^ 'SCF id' ] + ISUPSCFId class >> parameterValue [ ^ ISUPConstants parSCFId ] + ISUPSCFId class >> octalLength [ ^ 1 ] + ISUPSCFId class >> maxLength [ ^ nil ] + ISUPSCFId class >> spec [ ^ '3.71' ] +] + +MSGFixedField subclass: ISUPPivotCounter [ + + + + ISUPPivotCounter class >> parameterName [ ^ 'Pivot counter' ] + ISUPPivotCounter class >> parameterValue [ ^ ISUPConstants parPivotCounter ] + ISUPPivotCounter class >> octalLength [ ^ 1 ] + ISUPPivotCounter class >> spec [ ^ '3.93' ] +] + +MSGFixedField subclass: ISUPAccessDeliveryInformation [ + + + + ISUPAccessDeliveryInformation class >> parameterName [ ^ 'Access delivery information' ] + ISUPAccessDeliveryInformation class >> parameterValue [ ^ ISUPConstants parAccessDeliveryInformation ] + ISUPAccessDeliveryInformation class >> octalLength [ ^ 1 ] + ISUPAccessDeliveryInformation class >> spec [ ^ '3.2' ] +] + +MSGVariableField subclass: ISUPCallingPartyNumber [ + + + + ISUPCallingPartyNumber class >> parameterName [ ^ 'Calling party number' ] + ISUPCallingPartyNumber class >> parameterValue [ ^ ISUPConstants parCallingPartyNumber ] + ISUPCallingPartyNumber class >> octalLength [ ^ 2 ] + ISUPCallingPartyNumber class >> maxLength [ ^ nil ] + ISUPCallingPartyNumber class >> spec [ ^ '3.10' ] +] + +MSGFixedField subclass: ISUPSignallingPointCode [ + + + + ISUPSignallingPointCode class >> parameterName [ ^ 'Signalling point code' ] + ISUPSignallingPointCode class >> parameterValue [ ^ ISUPConstants parSignallingPointCode ] + ISUPSignallingPointCode class >> octalLength [ ^ 2 ] + ISUPSignallingPointCode class >> spec [ ^ '3.50' ] +] + +MSGFixedField subclass: ISUPMLPPPrecedence [ + + + + ISUPMLPPPrecedence class >> parameterName [ ^ 'MLPP precedence' ] + ISUPMLPPPrecedence class >> parameterValue [ ^ ISUPConstants parMLPPPrecedence ] + ISUPMLPPPrecedence class >> octalLength [ ^ 6 ] + ISUPMLPPPrecedence class >> spec [ ^ '3.34' ] +] + +MSGVariableField subclass: ISUPForwardGVNS [ + + + + ISUPForwardGVNS class >> parameterName [ ^ 'Forward GVNS' ] + ISUPForwardGVNS class >> parameterValue [ ^ ISUPConstants parForwardGVNS ] + ISUPForwardGVNS class >> octalLength [ ^ 3 ] + ISUPForwardGVNS class >> maxLength [ ^ 24 ] + ISUPForwardGVNS class >> spec [ ^ '3.66' ] +] + +MSGVariableField subclass: ISUPTransitNetworkSelection [ + + + + ISUPTransitNetworkSelection class >> parameterName [ ^ 'Transit network selection' ] + ISUPTransitNetworkSelection class >> parameterValue [ ^ ISUPConstants parTransitNetworkSelection ] + ISUPTransitNetworkSelection class >> octalLength [ ^ 2 ] + ISUPTransitNetworkSelection class >> maxLength [ ^ nil ] + ISUPTransitNetworkSelection class >> spec [ ^ '3.53' ] +] + +MSGVariableField subclass: ISUPDisplayInformation [ + + + + ISUPDisplayInformation class >> parameterName [ ^ 'Display information' ] + ISUPDisplayInformation class >> parameterValue [ ^ ISUPConstants parDisplayInformation ] + ISUPDisplayInformation class >> octalLength [ ^ 1 ] + ISUPDisplayInformation class >> maxLength [ ^ nil ] + ISUPDisplayInformation class >> spec [ ^ '3.77' ] +] + +MSGFixedField subclass: ISUPCallReference [ + + + + ISUPCallReference class >> parameterName [ ^ 'Call reference' ] + ISUPCallReference class >> parameterValue [ ^ ISUPConstants parCallReference ] + ISUPCallReference class >> octalLength [ ^ 5 ] + ISUPCallReference class >> spec [ ^ '3.8' ] +] + +MSGVariableField subclass: ISUPUserToUserInformation [ + + + + ISUPUserToUserInformation class >> parameterName [ ^ 'User-to-user information' ] + ISUPUserToUserInformation class >> parameterValue [ ^ ISUPConstants parUserToUserInformation ] + ISUPUserToUserInformation class >> octalLength [ ^ 1 ] + ISUPUserToUserInformation class >> maxLength [ ^ 129 ] + ISUPUserToUserInformation class >> spec [ ^ '3.61' ] +] + +MSGVariableField subclass: ISUPConnectedNumber [ + + + + ISUPConnectedNumber class >> parameterName [ ^ 'Connected number' ] + ISUPConnectedNumber class >> parameterValue [ ^ ISUPConstants parConnectedNumber ] + ISUPConnectedNumber class >> octalLength [ ^ 2 ] + ISUPConnectedNumber class >> maxLength [ ^ nil ] + ISUPConnectedNumber class >> spec [ ^ '3.16' ] +] + +MSGFixedField subclass: ISUPTransmissionMediumUsed [ + + + + ISUPTransmissionMediumUsed class >> parameterName [ ^ 'Transmission medium used' ] + ISUPTransmissionMediumUsed class >> parameterValue [ ^ ISUPConstants parTransmissionMediumUsed ] + ISUPTransmissionMediumUsed class >> octalLength [ ^ 1 ] + ISUPTransmissionMediumUsed class >> spec [ ^ '3.56' ] +] + +MSGFixedField subclass: ISUPInformationRequestIndicators [ + + + + ISUPInformationRequestIndicators class >> parameterName [ ^ 'Information request indicators' ] + ISUPInformationRequestIndicators class >> parameterValue [ ^ ISUPConstants parInformationRequestIndicators ] + ISUPInformationRequestIndicators class >> octalLength [ ^ 2 ] + ISUPInformationRequestIndicators class >> spec [ ^ '3.29' ] +] + +MSGVariableField subclass: ISUPApplicationTransportParameter [ + + + + ISUPApplicationTransportParameter class >> parameterName [ ^ 'Application transport parameter' ] + ISUPApplicationTransportParameter class >> parameterValue [ ^ ISUPConstants parApplicationTransportParameter ] + ISUPApplicationTransportParameter class >> octalLength [ ^ 3 ] + ISUPApplicationTransportParameter class >> maxLength [ ^ nil ] + ISUPApplicationTransportParameter class >> spec [ ^ '3.82' ] +] + +MSGVariableField subclass: ISUPCallDiversionTreatmentIndicators [ + + + + ISUPCallDiversionTreatmentIndicators class >> parameterName [ ^ 'Call diversion treatment indicators' ] + ISUPCallDiversionTreatmentIndicators class >> parameterValue [ ^ ISUPConstants parCallDiversionTreatmentIndicators ] + ISUPCallDiversionTreatmentIndicators class >> octalLength [ ^ 1 ] + ISUPCallDiversionTreatmentIndicators class >> maxLength [ ^ nil ] + ISUPCallDiversionTreatmentIndicators class >> spec [ ^ '3.72' ] +] + +MSGVariableField subclass: ISUPParameterCompatibilityInformation [ + + + + ISUPParameterCompatibilityInformation class >> parameterName [ ^ 'Parameter compatibility information' ] + ISUPParameterCompatibilityInformation class >> parameterValue [ ^ ISUPConstants parParameterCompatibilityInformation ] + ISUPParameterCompatibilityInformation class >> octalLength [ ^ 2 ] + ISUPParameterCompatibilityInformation class >> maxLength [ ^ nil ] + ISUPParameterCompatibilityInformation class >> spec [ ^ '3.41' ] +] + +MSGVariableField subclass: ISUPNetworkRoutingNumber [ + + + + ISUPNetworkRoutingNumber class >> parameterName [ ^ 'Network routing number' ] + ISUPNetworkRoutingNumber class >> parameterValue [ ^ ISUPConstants parNetworkRoutingNumber ] + ISUPNetworkRoutingNumber class >> octalLength [ ^ 2 ] + ISUPNetworkRoutingNumber class >> maxLength [ ^ nil ] + ISUPNetworkRoutingNumber class >> spec [ ^ '3.90' ] +] + +MSGVariableField subclass: ISUPAccessTransport [ + + + + ISUPAccessTransport class >> parameterName [ ^ 'Access transport' ] + ISUPAccessTransport class >> parameterValue [ ^ ISUPConstants parAccessTransport ] + ISUPAccessTransport class >> octalLength [ ^ 1 ] + ISUPAccessTransport class >> maxLength [ ^ nil ] + ISUPAccessTransport class >> spec [ ^ '3.3' ] +] + +MSGFixedField subclass: ISUPCircuitGroupSupervisionMessageType [ + + + + ISUPCircuitGroupSupervisionMessageType class >> parameterName [ ^ 'Circuit group supervision message type' ] + ISUPCircuitGroupSupervisionMessageType class >> parameterValue [ ^ ISUPConstants parCircuitGroupSupervisionMessageType ] + ISUPCircuitGroupSupervisionMessageType class >> octalLength [ ^ 1 ] + ISUPCircuitGroupSupervisionMessageType class >> spec [ ^ '3.13' ] +] + +MSGVariableField subclass: ISUPUserTeleserviceInformation [ + + + + ISUPUserTeleserviceInformation class >> parameterName [ ^ 'User teleservice information' ] + ISUPUserTeleserviceInformation class >> parameterValue [ ^ ISUPConstants parUserTeleserviceInformation ] + ISUPUserTeleserviceInformation class >> octalLength [ ^ 2 ] + ISUPUserTeleserviceInformation class >> maxLength [ ^ 3 ] + ISUPUserTeleserviceInformation class >> spec [ ^ '3.59' ] +] + +MSGVariableField subclass: ISUPHTRInformation [ + + + + ISUPHTRInformation class >> parameterName [ ^ 'HTR information' ] + ISUPHTRInformation class >> parameterValue [ ^ ISUPConstants parHTRInformation ] + ISUPHTRInformation class >> octalLength [ ^ 2 ] + ISUPHTRInformation class >> maxLength [ ^ nil ] + ISUPHTRInformation class >> spec [ ^ '3.89' ] +] + +MSGFixedField subclass: ISUPInformationIndicators [ + + + + ISUPInformationIndicators class >> parameterName [ ^ 'Information indicators' ] + ISUPInformationIndicators class >> parameterValue [ ^ ISUPConstants parInformationIndicators ] + ISUPInformationIndicators class >> octalLength [ ^ 2 ] + ISUPInformationIndicators class >> spec [ ^ '3.28' ] +] + +MSGFixedField subclass: ISUPCallDiversionInformation [ + + + + ISUPCallDiversionInformation class >> parameterName [ ^ 'Call diversion information' ] + ISUPCallDiversionInformation class >> parameterValue [ ^ ISUPConstants parCallDiversionInformation ] + ISUPCallDiversionInformation class >> octalLength [ ^ 1 ] + ISUPCallDiversionInformation class >> spec [ ^ '3.6' ] +] + +MSGVariableField subclass: ISUPCircuitStateIndicator [ + + + + ISUPCircuitStateIndicator class >> parameterName [ ^ 'Circuit state indicator' ] + ISUPCircuitStateIndicator class >> parameterValue [ ^ ISUPConstants parCircuitStateIndicator ] + ISUPCircuitStateIndicator class >> octalLength [ ^ 1 ] + ISUPCircuitStateIndicator class >> maxLength [ ^ 32 ] + ISUPCircuitStateIndicator class >> spec [ ^ '3.14' ] +] + +MSGFixedField subclass: ISUPLoopPreventionIndicators [ + + + + ISUPLoopPreventionIndicators class >> parameterName [ ^ 'Loop prevention indicators' ] + ISUPLoopPreventionIndicators class >> parameterValue [ ^ ISUPConstants parLoopPreventionIndicators ] + ISUPLoopPreventionIndicators class >> octalLength [ ^ 1 ] + ISUPLoopPreventionIndicators class >> spec [ ^ '3.67' ] +] + +MSGVariableField subclass: ISUPChargedPartyIdentification [ + + + + ISUPChargedPartyIdentification class >> parameterName [ ^ 'Charged party identification' ] + ISUPChargedPartyIdentification class >> parameterValue [ ^ ISUPConstants parChargedPartyIdentification ] + ISUPChargedPartyIdentification class >> octalLength [ ^ 1 ] + ISUPChargedPartyIdentification class >> maxLength [ ^ nil ] + ISUPChargedPartyIdentification class >> spec [ ^ '3.75' ] +] + +MSGVariableField subclass: ISUPLocationNumber [ + + + + ISUPLocationNumber class >> parameterName [ ^ 'Location number' ] + ISUPLocationNumber class >> parameterValue [ ^ ISUPConstants parLocationNumber ] + ISUPLocationNumber class >> octalLength [ ^ 2 ] + ISUPLocationNumber class >> maxLength [ ^ nil ] + ISUPLocationNumber class >> spec [ ^ '3.30' ] +] + +MSGVariableField subclass: ISUPNumberPortabilityForwardInformation [ + + + + ISUPNumberPortabilityForwardInformation class >> parameterName [ ^ 'Number portability forward information' ] + ISUPNumberPortabilityForwardInformation class >> parameterValue [ ^ ISUPConstants parNumberPortabilityForwardInformation ] + ISUPNumberPortabilityForwardInformation class >> octalLength [ ^ -1 ] + ISUPNumberPortabilityForwardInformation class >> maxLength [ ^ nil ] + ISUPNumberPortabilityForwardInformation class >> spec [ ^ '3.101' ] +] + +MSGFixedField subclass: ISUPTransmissionMediumRequirement [ + + + + ISUPTransmissionMediumRequirement class >> parameterName [ ^ 'Transmission medium requirement' ] + ISUPTransmissionMediumRequirement class >> parameterValue [ ^ ISUPConstants parTransmissionMediumRequirement ] + ISUPTransmissionMediumRequirement class >> octalLength [ ^ 1 ] + ISUPTransmissionMediumRequirement class >> spec [ ^ '3.54' ] +] + +MSGFixedField subclass: ISUPEchoControlInformation [ + + + + ISUPEchoControlInformation class >> parameterName [ ^ 'Echo control information' ] + ISUPEchoControlInformation class >> parameterValue [ ^ ISUPConstants parEchoControlInformation ] + ISUPEchoControlInformation class >> octalLength [ ^ 1 ] + ISUPEchoControlInformation class >> spec [ ^ '3.19' ] +] + +MSGVariableField subclass: ISUPCalledPartyNumber [ + + + + ISUPCalledPartyNumber class >> parameterName [ ^ 'Called party number' ] + ISUPCalledPartyNumber class >> parameterValue [ ^ ISUPConstants parCalledPartyNumber ] + ISUPCalledPartyNumber class >> octalLength [ ^ 3 ] + ISUPCalledPartyNumber class >> maxLength [ ^ nil ] + ISUPCalledPartyNumber class >> spec [ ^ '3.9' ] +] + +MSGFixedField subclass: ISUPRedirectionNumberRestriction [ + + + + ISUPRedirectionNumberRestriction class >> parameterName [ ^ 'Redirection number restriction' ] + ISUPRedirectionNumberRestriction class >> parameterValue [ ^ ISUPConstants parRedirectionNumberRestriction ] + ISUPRedirectionNumberRestriction class >> octalLength [ ^ 1 ] + ISUPRedirectionNumberRestriction class >> spec [ ^ '3.47' ] +] + +MSGVariableField subclass: ISUPUIDActionIndicators [ + + + + ISUPUIDActionIndicators class >> parameterName [ ^ 'UID action indicators' ] + ISUPUIDActionIndicators class >> parameterValue [ ^ ISUPConstants parUIDActionIndicators ] + ISUPUIDActionIndicators class >> octalLength [ ^ 1 ] + ISUPUIDActionIndicators class >> maxLength [ ^ nil ] + ISUPUIDActionIndicators class >> spec [ ^ '3.78' ] +] + +MSGFixedField subclass: ISUPPivotCapability [ + + + + ISUPPivotCapability class >> parameterName [ ^ 'Pivot capability' ] + ISUPPivotCapability class >> parameterValue [ ^ ISUPConstants parPivotCapability ] + ISUPPivotCapability class >> octalLength [ ^ 1 ] + ISUPPivotCapability class >> spec [ ^ '3.84' ] +] + +MSGFixedField subclass: ISUPRange [ + + + + ISUPRange class >> parameterName [ ^ 'Range' ] + ISUPRange class >> parameterValue [ ^ ISUPConstants parRange ] + ISUPRange class >> octalLength [ ^ 1 ] + ISUPRange class >> spec [ ^ '3.43b' ] +] + +MSGFixedField subclass: ISUPFacilityIndicator [ + + + + ISUPFacilityIndicator class >> parameterName [ ^ 'Facility indicator' ] + ISUPFacilityIndicator class >> parameterValue [ ^ ISUPConstants parFacilityIndicator ] + ISUPFacilityIndicator class >> octalLength [ ^ 1 ] + ISUPFacilityIndicator class >> spec [ ^ '3.22' ] +] + +MSGVariableField subclass: ISUPPivotRoutingForwardInformation [ + + + + ISUPPivotRoutingForwardInformation class >> parameterName [ ^ 'Pivot routing forward information' ] + ISUPPivotRoutingForwardInformation class >> parameterValue [ ^ ISUPConstants parPivotRoutingForwardInformation ] + ISUPPivotRoutingForwardInformation class >> octalLength [ ^ 1 ] + ISUPPivotRoutingForwardInformation class >> maxLength [ ^ nil ] + ISUPPivotRoutingForwardInformation class >> spec [ ^ '3.94' ] +] + +MSGFixedField subclass: ISUPCCNRPossibleIndicator [ + + + + ISUPCCNRPossibleIndicator class >> parameterName [ ^ 'CCNR possible indicator' ] + ISUPCCNRPossibleIndicator class >> parameterValue [ ^ ISUPConstants parCCNRPossibleIndicator ] + ISUPCCNRPossibleIndicator class >> octalLength [ ^ 1 ] + ISUPCCNRPossibleIndicator class >> spec [ ^ '3.83' ] +] + +MSGFixedField subclass: ISUPOriginationISCPointCode [ + + + + ISUPOriginationISCPointCode class >> parameterName [ ^ 'Origination ISC point code' ] + ISUPOriginationISCPointCode class >> parameterValue [ ^ ISUPConstants parOriginationISCPointCode ] + ISUPOriginationISCPointCode class >> octalLength [ ^ 2 ] + ISUPOriginationISCPointCode class >> spec [ ^ '3.40' ] +] + +MSGVariableField subclass: ISUPMessageCompatibilityInformation [ + + + + ISUPMessageCompatibilityInformation class >> parameterName [ ^ 'Message compatibility information' ] + ISUPMessageCompatibilityInformation class >> parameterValue [ ^ ISUPConstants parMessageCompatibilityInformation ] + ISUPMessageCompatibilityInformation class >> octalLength [ ^ 1 ] + ISUPMessageCompatibilityInformation class >> maxLength [ ^ nil ] + ISUPMessageCompatibilityInformation class >> spec [ ^ '3.33' ] +] + +MSGVariableField subclass: ISUPRedirectForwardInformation [ + + + + ISUPRedirectForwardInformation class >> parameterName [ ^ 'Redirect forward information' ] + ISUPRedirectForwardInformation class >> parameterValue [ ^ ISUPConstants parRedirectForwardInformation ] + ISUPRedirectForwardInformation class >> octalLength [ ^ 1 ] + ISUPRedirectForwardInformation class >> maxLength [ ^ nil ] + ISUPRedirectForwardInformation class >> spec [ ^ '3.99' ] +] + +MSGFixedField subclass: ISUPGenericNotificationIndicator [ + + + + ISUPGenericNotificationIndicator class >> parameterName [ ^ 'Generic notification indicator' ] + ISUPGenericNotificationIndicator class >> parameterValue [ ^ ISUPConstants parGenericNotificationIndicator ] + ISUPGenericNotificationIndicator class >> octalLength [ ^ 1 ] + ISUPGenericNotificationIndicator class >> spec [ ^ '3.25' ] +] + +MSGFixedField subclass: ISUPUserToUserIndicators [ + + + + ISUPUserToUserIndicators class >> parameterName [ ^ 'User-to-user indicators' ] + ISUPUserToUserIndicators class >> parameterValue [ ^ ISUPConstants parUserToUserIndicators ] + ISUPUserToUserIndicators class >> octalLength [ ^ 1 ] + ISUPUserToUserIndicators class >> spec [ ^ '3.60' ] +] + +MSGVariableField subclass: ISUPNetworkSpecificFacility [ + + + + ISUPNetworkSpecificFacility class >> parameterName [ ^ 'Network specific facility' ] + ISUPNetworkSpecificFacility class >> parameterValue [ ^ ISUPConstants parNetworkSpecificFacility ] + ISUPNetworkSpecificFacility class >> octalLength [ ^ 2 ] + ISUPNetworkSpecificFacility class >> maxLength [ ^ nil ] + ISUPNetworkSpecificFacility class >> spec [ ^ '3.36' ] +] + +MSGFixedField subclass: ISUPMCIDRequestIndicators [ + + + + ISUPMCIDRequestIndicators class >> parameterName [ ^ 'MCID request indicators' ] + ISUPMCIDRequestIndicators class >> parameterValue [ ^ ISUPConstants parMCIDRequestIndicators ] + ISUPMCIDRequestIndicators class >> octalLength [ ^ 1 ] + ISUPMCIDRequestIndicators class >> spec [ ^ '3.31' ] +] + +MSGFixedField subclass: ISUPTransmissionMediumRequirementPrime [ + + + + ISUPTransmissionMediumRequirementPrime class >> parameterName [ ^ 'Transmission medium requirement prime' ] + ISUPTransmissionMediumRequirementPrime class >> parameterValue [ ^ ISUPConstants parTransmissionMediumRequirementPrime ] + ISUPTransmissionMediumRequirementPrime class >> octalLength [ ^ 1 ] + ISUPTransmissionMediumRequirementPrime class >> spec [ ^ '3.55' ] +] + +MSGFixedField subclass: ISUPContinuityIndicators [ + + + + ISUPContinuityIndicators class >> parameterName [ ^ 'Continuity indicators' ] + ISUPContinuityIndicators class >> parameterValue [ ^ ISUPConstants parContinuityIndicators ] + ISUPContinuityIndicators class >> octalLength [ ^ 1 ] + ISUPContinuityIndicators class >> spec [ ^ '3.18' ] +] + +MSGVariableField subclass: ISUPCCSS [ + + + + ISUPCCSS class >> parameterName [ ^ 'CCSS' ] + ISUPCCSS class >> parameterValue [ ^ ISUPConstants parCCSS ] + ISUPCCSS class >> octalLength [ ^ 1 ] + ISUPCCSS class >> maxLength [ ^ nil ] + ISUPCCSS class >> spec [ ^ '3.63' ] +] + +MSGVariableField subclass: ISUPUIDCapabilityIndicators [ + + + + ISUPUIDCapabilityIndicators class >> parameterName [ ^ 'UID capability indicators' ] + ISUPUIDCapabilityIndicators class >> parameterValue [ ^ ISUPConstants parUIDCapabilityIndicators ] + ISUPUIDCapabilityIndicators class >> octalLength [ ^ 1 ] + ISUPUIDCapabilityIndicators class >> maxLength [ ^ nil ] + ISUPUIDCapabilityIndicators class >> spec [ ^ '3.79' ] +] + +MSGVariableField subclass: ISUPUserServiceInformationPrime [ + + + + ISUPUserServiceInformationPrime class >> parameterName [ ^ 'User service information prime' ] + ISUPUserServiceInformationPrime class >> parameterValue [ ^ ISUPConstants parUserServiceInformationPrime ] + ISUPUserServiceInformationPrime class >> octalLength [ ^ 2 ] + ISUPUserServiceInformationPrime class >> maxLength [ ^ 11 ] + ISUPUserServiceInformationPrime class >> spec [ ^ '3.58' ] +] + +MSGVariableField subclass: ISUPGenericReference [ + + + + ISUPGenericReference class >> parameterName [ ^ 'Generic reference' ] + ISUPGenericReference class >> parameterValue [ ^ ISUPConstants parGenericReference ] + ISUPGenericReference class >> octalLength [ ^ 3 ] + ISUPGenericReference class >> maxLength [ ^ nil ] + ISUPGenericReference class >> spec [ ^ '3.27' ] +] + +MSGFixedField subclass: ISUPHopCounter [ + + + + ISUPHopCounter class >> parameterName [ ^ 'Hop counter' ] + ISUPHopCounter class >> parameterValue [ ^ ISUPConstants parHopCounter ] + ISUPHopCounter class >> octalLength [ ^ 1 ] + ISUPHopCounter class >> spec [ ^ '3.80' ] +] + +MSGFixedField subclass: ISUPBackwardCallIndicators [ + + + + ISUPBackwardCallIndicators class >> parameterName [ ^ 'Backward call indicators' ] + ISUPBackwardCallIndicators class >> parameterValue [ ^ ISUPConstants parBackwardCallIndicators ] + ISUPBackwardCallIndicators class >> octalLength [ ^ 2 ] + ISUPBackwardCallIndicators class >> spec [ ^ '3.5' ] +] + +MSGFixedField subclass: ISUPClosedUserGroupInterlockCode [ + + + + ISUPClosedUserGroupInterlockCode class >> parameterName [ ^ 'Closed user group interlock code' ] + ISUPClosedUserGroupInterlockCode class >> parameterValue [ ^ ISUPConstants parClosedUserGroupInterlockCode ] + ISUPClosedUserGroupInterlockCode class >> octalLength [ ^ 4 ] + ISUPClosedUserGroupInterlockCode class >> spec [ ^ '3.15' ] +] + +MSGVariableField subclass: ISUPRangeAndStatus [ + + + + ISUPRangeAndStatus class >> parameterName [ ^ 'Range and status' ] + ISUPRangeAndStatus class >> parameterValue [ ^ ISUPConstants parRangeAndStatus ] + ISUPRangeAndStatus class >> octalLength [ ^ 2 ] + ISUPRangeAndStatus class >> maxLength [ ^ 33 ] + ISUPRangeAndStatus class >> spec [ ^ '3.43' ] +] + +MSGFixedField subclass: ISUPRedirectStatus [ + + + + ISUPRedirectStatus class >> parameterName [ ^ 'Redirect status' ] + ISUPRedirectStatus class >> parameterValue [ ^ ISUPConstants parRedirectStatus ] + ISUPRedirectStatus class >> octalLength [ ^ 1 ] + ISUPRedirectStatus class >> spec [ ^ '3.98' ] +] + +MSGVariableField subclass: ISUPCallOfferingTreatmentIndicators [ + + + + ISUPCallOfferingTreatmentIndicators class >> parameterName [ ^ 'Call offering treatment indicators' ] + ISUPCallOfferingTreatmentIndicators class >> parameterValue [ ^ ISUPConstants parCallOfferingTreatmentIndicators ] + ISUPCallOfferingTreatmentIndicators class >> octalLength [ ^ 1 ] + ISUPCallOfferingTreatmentIndicators class >> maxLength [ ^ nil ] + ISUPCallOfferingTreatmentIndicators class >> spec [ ^ '3.74' ] +] + +MSGVariableField subclass: ISUPServiceActivation [ + + + + ISUPServiceActivation class >> parameterName [ ^ 'Service activation' ] + ISUPServiceActivation class >> parameterValue [ ^ ISUPConstants parServiceActivation ] + ISUPServiceActivation class >> octalLength [ ^ 1 ] + ISUPServiceActivation class >> maxLength [ ^ nil ] + ISUPServiceActivation class >> spec [ ^ '3.49' ] +] + +MSGVariableField subclass: ISUPGenericNumber [ + + + + ISUPGenericNumber class >> parameterName [ ^ 'Generic number' ] + ISUPGenericNumber class >> parameterValue [ ^ ISUPConstants parGenericNumber ] + ISUPGenericNumber class >> octalLength [ ^ 3 ] + ISUPGenericNumber class >> maxLength [ ^ nil ] + ISUPGenericNumber class >> spec [ ^ '3.26' ] +] + +MSGVariableField subclass: ISUPRedirectingNumber [ + + + + ISUPRedirectingNumber class >> parameterName [ ^ 'Redirecting number' ] + ISUPRedirectingNumber class >> parameterValue [ ^ ISUPConstants parRedirectingNumber ] + ISUPRedirectingNumber class >> octalLength [ ^ 2 ] + ISUPRedirectingNumber class >> maxLength [ ^ nil ] + ISUPRedirectingNumber class >> spec [ ^ '3.44' ] +] + +MSGFixedField subclass: ISUPOptionalBackwardCallIndicators [ + + + + ISUPOptionalBackwardCallIndicators class >> parameterName [ ^ 'Optional backward call indicators' ] + ISUPOptionalBackwardCallIndicators class >> parameterValue [ ^ ISUPConstants parOptionalBackwardCallIndicators ] + ISUPOptionalBackwardCallIndicators class >> octalLength [ ^ 1 ] + ISUPOptionalBackwardCallIndicators class >> spec [ ^ '3.37' ] +] + +MSGVariableField subclass: ISUPOriginalCalledINNumber [ + + + + ISUPOriginalCalledINNumber class >> parameterName [ ^ 'Original called IN number' ] + ISUPOriginalCalledINNumber class >> parameterValue [ ^ ISUPConstants parOriginalCalledINNumber ] + ISUPOriginalCalledINNumber class >> octalLength [ ^ 2 ] + ISUPOriginalCalledINNumber class >> maxLength [ ^ nil ] + ISUPOriginalCalledINNumber class >> spec [ ^ '3.87' ] +] + +MSGFixedField subclass: ISUPEventInformation [ + + + + ISUPEventInformation class >> parameterName [ ^ 'Event information' ] + ISUPEventInformation class >> parameterValue [ ^ ISUPConstants parEventInformation ] + ISUPEventInformation class >> octalLength [ ^ 1 ] + ISUPEventInformation class >> spec [ ^ '3.21' ] +] + +MSGVariableField subclass: ISUPPivotRoutingBackwardInformation [ + + + + ISUPPivotRoutingBackwardInformation class >> parameterName [ ^ 'Pivot routing backward information' ] + ISUPPivotRoutingBackwardInformation class >> parameterValue [ ^ ISUPConstants parPivotRoutingBackwardInformation ] + ISUPPivotRoutingBackwardInformation class >> octalLength [ ^ 1 ] + ISUPPivotRoutingBackwardInformation class >> maxLength [ ^ nil ] + ISUPPivotRoutingBackwardInformation class >> spec [ ^ '3.95' ] +] + +MSGVariableField subclass: ISUPCircuitAssignmentMap [ + + + + ISUPCircuitAssignmentMap class >> parameterName [ ^ 'Circuit assignment map' ] + ISUPCircuitAssignmentMap class >> parameterValue [ ^ ISUPConstants parCircuitAssignmentMap ] + ISUPCircuitAssignmentMap class >> octalLength [ ^ 4 ] + ISUPCircuitAssignmentMap class >> maxLength [ ^ 5 ] + ISUPCircuitAssignmentMap class >> spec [ ^ '3.69' ] +] + +MSGFixedField subclass: ISUPMCIDResponseIndicators [ + + + + ISUPMCIDResponseIndicators class >> parameterName [ ^ 'MCID response indicators' ] + ISUPMCIDResponseIndicators class >> parameterValue [ ^ ISUPConstants parMCIDResponseIndicators ] + ISUPMCIDResponseIndicators class >> octalLength [ ^ 1 ] + ISUPMCIDResponseIndicators class >> spec [ ^ '3.32' ] +] + +MSGVariableField subclass: ISUPCallTransferNumber [ + + + + ISUPCallTransferNumber class >> parameterName [ ^ 'Call transfer number' ] + ISUPCallTransferNumber class >> parameterValue [ ^ ISUPConstants parCallTransferNumber ] + ISUPCallTransferNumber class >> octalLength [ ^ 2 ] + ISUPCallTransferNumber class >> maxLength [ ^ nil ] + ISUPCallTransferNumber class >> spec [ ^ '3.64' ] +] + +"MSGs for ISUP" +ISUPMessage subclass: ISUPACM [ + + + + ISUPACM class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgACM) + addFixed: ISUPBackwardCallIndicators; + addOptional: ISUPOptionalBackwardCallIndicators; + addOptional: ISUPCallReference; + addOptional: ISUPCauseIndicators; + addOptional: ISUPUserToUserIndicators; + addOptional: ISUPUserToUserInformation; + addOptional: ISUPAccessTransport; + addOptionals: ISUPGenericNotificationIndicator; + addOptional: ISUPTransmissionMediumUsed; + addOptional: ISUPEchoControlInformation; + addOptional: ISUPAccessDeliveryInformation; + addOptional: ISUPRedirectionNumber; + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPCallDiversionInformation; + addOptional: ISUPNetworkSpecificFacility; + addOptional: ISUPRemoteOperations; + addOptional: ISUPServiceActivation; + addOptional: ISUPRedirectionNumberRestriction; + addOptional: ISUPConferenceTreatmentIndicators; + addOptional: ISUPUIDActionIndicators; + addOptionals: ISUPApplicationTransportParameter; + addOptional: ISUPCCNRPossibleIndicator; + addOptional: ISUPHTRInformation; + addOptional: ISUPPivotRoutingBackwardInformation; + addOptional: ISUPRedirectStatus; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPAMN [ + + + + ISUPAMN class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgAMN) + addOptional: ISUPBackwardCallIndicators; + addOptional: ISUPOptionalBackwardCallIndicators; + addOptional: ISUPCallReference; + addOptional: ISUPUserToUserIndicators; + addOptional: ISUPUserToUserInformation; + addOptional: ISUPConnectedNumber; + addOptional: ISUPAccessTransport; + addOptional: ISUPAccessDeliveryInformation; + addOptionals: ISUPGenericNotificationIndicator; + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPBackwardGVNS; + addOptional: ISUPCallHistoryInformation; + addOptional: ISUPGenericNumber; + addOptional: ISUPTransmissionMediumUsed; + addOptional: ISUPNetworkSpecificFacility; + addOptional: ISUPRemoteOperations; + addOptional: ISUPRedirectionNumber; + addOptional: ISUPServiceActivation; + addOptional: ISUPEchoControlInformation; + addOptional: ISUPRedirectionNumberRestriction; + addOptional: ISUPDisplayInformation; + addOptional: ISUPConferenceTreatmentIndicators; + addOptionals: ISUPApplicationTransportParameter; + addOptional: ISUPPivotRoutingBackwardInformation; + addOptional: ISUPRedirectStatus; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPAPT [ + + + + ISUPAPT class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgAPT) + addOptional: ISUPMessageCompatibilityInformation; + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPApplicationTransportParameter; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPBLO [ + + + + ISUPBLO class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgBLO) + yourself. + ] +] + + +ISUPMessage subclass: ISUPCFN [ + + + + ISUPCFN class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgCFN) + addVariable: ISUPCauseIndicators; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPCGB [ + + + + ISUPCGB class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgCGB) + addFixed: ISUPCircuitGroupSupervisionMessageType; + addVariable: ISUPRangeAndStatus; + yourself. + ] +] + + +ISUPMessage subclass: ISUPCON [ + + + + ISUPCON class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgCON) + addFixed: ISUPBackwardCallIndicators; + addOptional: ISUPOptionalBackwardCallIndicators; + addOptional: ISUPBackwardGVNS; + addOptional: ISUPConnectedNumber; + addOptional: ISUPCallReference; + addOptional: ISUPUserToUserIndicators; + addOptional: ISUPUserToUserInformation; + addOptional: ISUPAccessTransport; + addOptional: ISUPNetworkSpecificFacility; + addOptionals: ISUPGenericNotificationIndicator; + addOptional: ISUPRemoteOperations; + addOptional: ISUPTransmissionMediumUsed; + addOptional: ISUPEchoControlInformation; + addOptional: ISUPAccessDeliveryInformation; + addOptional: ISUPCallHistoryInformation; + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPServiceActivation; + addOptional: ISUPGenericNumber; + addOptional: ISUPRedirectionNumberRestriction; + addOptional: ISUPConferenceTreatmentIndicators; + addOptionals: ISUPApplicationTransportParameter; + addOptional: ISUPHTRInformation; + addOptional: ISUPPivotRoutingBackwardInformation; + addOptional: ISUPRedirectStatus; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPCOT [ + + + + ISUPCOT class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgCOT) + addFixed: ISUPContinuityIndicators; + yourself. + ] +] + + +ISUPMessage subclass: ISUPCPG [ + + + + ISUPCPG class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgCPG) + addFixed: ISUPEventInformation; + addOptional: ISUPCauseIndicators; + addOptional: ISUPCallReference; + addOptional: ISUPBackwardCallIndicators; + addOptional: ISUPOptionalBackwardCallIndicators; + addOptional: ISUPAccessTransport; + addOptional: ISUPUserToUserIndicators; + addOptional: ISUPRedirectionNumber; + addOptional: ISUPUserToUserInformation; + addOptionals: ISUPGenericNotificationIndicator; + addOptional: ISUPNetworkSpecificFacility; + addOptional: ISUPRemoteOperations; + addOptional: ISUPTransmissionMediumUsed; + addOptional: ISUPAccessDeliveryInformation; + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPCallDiversionInformation; + addOptional: ISUPServiceActivation; + addOptional: ISUPRedirectionNumberRestriction; + addOptional: ISUPCallTransferNumber; + addOptional: ISUPEchoControlInformation; + addOptional: ISUPConnectedNumber; + addOptional: ISUPBackwardGVNS; + addOptional: ISUPGenericNumber; + addOptional: ISUPCallHistoryInformation; + addOptional: ISUPConferenceTreatmentIndicators; + addOptional: ISUPUIDActionIndicators; + addOptionals: ISUPApplicationTransportParameter; + addOptional: ISUPCCNRPossibleIndicator; + addOptional: ISUPPivotRoutingBackwardInformation; + addOptional: ISUPRedirectStatus; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPCQR [ + + + + ISUPCQR class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgCQR) + addVariable: ISUPRange; + addVariable: ISUPCircuitStateIndicator; + yourself. + ] +] + + +ISUPMessage subclass: ISUPFAA [ + + + + ISUPFAA class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgFAA) + addFixed: ISUPFacilityIndicator; + addOptional: ISUPUserToUserIndicators; + addOptional: ISUPCallReference; + addOptional: ISUPConnectionRequest; + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPFAC [ + + + + ISUPFAC class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgFAC) + addOptional: ISUPMessageCompatibilityInformation; + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPRemoteOperations; + addOptional: ISUPServiceActivation; + addOptional: ISUPCallTransferNumber; + addOptional: ISUPAccessTransport; + addOptional: ISUPGenericNotificationIndicator; + addOptional: ISUPRedirectionNumber; + addOptional: ISUPPivotRoutingIndicators; + addOptional: ISUPPivotStatus; + addOptional: ISUPPivotCounter; + addOptional: ISUPPivotRoutingBackwardInformation; + addOptional: ISUPRedirectStatus; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPFOT [ + + + + ISUPFOT class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgFOT) + addOptional: ISUPCallReference; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPFRJ [ + + + + ISUPFRJ class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgFRJ) + addFixed: ISUPFacilityIndicator; + addVariable: ISUPCauseIndicators; + addOptional: ISUPUserToUserIndicators; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPGRA [ + + + + ISUPGRA class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgGRA) + addVariable: ISUPRangeAndStatus; + yourself. + ] +] + + +ISUPMessage subclass: ISUPGRS [ + + + + ISUPGRS class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgGRS) + addVariable: ISUPRange; + yourself. + ] +] + + +ISUPMessage subclass: ISUPIAM [ + + + + ISUPIAM class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgIAM) + addFixed: ISUPNatureOfConnectionIndicators; + addFixed: ISUPForwardCallIndicators; + addFixed: ISUPCallingPartysCategory; + addFixed: ISUPTransmissionMediumRequirement; + addVariable: ISUPCalledPartyNumber; + addOptional: ISUPTransitNetworkSelection; + addOptional: ISUPCallReference; + addOptional: ISUPCallingPartyNumber; + addOptional: ISUPOptionalForwardCallIndicators; + addOptional: ISUPRedirectingNumber; + addOptional: ISUPRedirectionInformation; + addOptional: ISUPClosedUserGroupInterlockCode; + addOptional: ISUPConnectionRequest; + addOptional: ISUPOriginalCalledNumber; + addOptional: ISUPUserToUserInformation; + addOptional: ISUPAccessTransport; + addOptional: ISUPUserServiceInformation; + addOptional: ISUPUserToUserIndicators; + addOptional: ISUPGenericNumber; + addOptional: ISUPPropagationDelayCounter; + addOptional: ISUPUserServiceInformationPrime; + addOptional: ISUPNetworkSpecificFacility; + addOptionals: ISUPGenericDigits; + addOptional: ISUPOriginationISCPointCode; + addOptional: ISUPUserTeleserviceInformation; + addOptional: ISUPRemoteOperations; + addOptional: ISUPParameterCompatibilityInformation; + addOptionals: ISUPGenericNotificationIndicator; + addOptional: ISUPServiceActivation; + addOptional: ISUPGenericReference; + addOptional: ISUPMLPPPrecedence; + addOptional: ISUPTransmissionMediumRequirementPrime; + addOptional: ISUPLocationNumber; + addOptional: ISUPForwardGVNS; + addOptional: ISUPCCSS; + addOptional: ISUPNetworkManagementControls; + addOptional: ISUPCircuitAssignmentMap; + addOptional: ISUPCorrelationId; + addOptional: ISUPCallDiversionTreatmentIndicators; + addOptional: ISUPCalledINNumber; + addOptional: ISUPCallOfferingTreatmentIndicators; + addOptional: ISUPConferenceTreatmentIndicators; + addOptional: ISUPSCFId; + addOptional: ISUPUIDCapabilityIndicators; + addOptional: ISUPEchoControlInformation; + addOptional: ISUPHopCounter; + addOptional: ISUPCollectCallRequest; + addOptionals: ISUPApplicationTransportParameter; + addOptional: ISUPPivotCapability; + addOptional: ISUPCalledDirectoryNumber; + addOptional: ISUPOriginalCalledINNumber; + addOptional: ISUPCallingGeodeticLocation; + addOptional: ISUPNetworkRoutingNumber; + addOptional: ISUPQoRCapability; + addOptional: ISUPPivotCounter; + addOptional: ISUPPivotRoutingForwardInformation; + addOptional: ISUPRedirectCapability; + addOptional: ISUPRedirectCounter; + addOptional: ISUPRedirectStatus; + addOptional: ISUPRedirectForwardInformation; + addOptional: ISUPNumberPortabilityForwardInformation; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPIDR [ + + + + ISUPIDR class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgIDR) + addOptional: ISUPMCIDRequestIndicators; + addOptional: ISUPMessageCompatibilityInformation; + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPIDS [ + + + + ISUPIDS class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgIDS) + addOptional: ISUPMCIDResponseIndicators; + addOptional: ISUPMessageCompatibilityInformation; + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPCallingPartyNumber; + addOptional: ISUPAccessTransport; + addOptional: ISUPGenericNumber; + addOptional: ISUPChargedPartyIdentification; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPINF [ + + + + ISUPINF class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgINF) + addFixed: ISUPInformationIndicators; + addOptional: ISUPCallingPartysCategory; + addOptional: ISUPCallingPartyNumber; + addOptional: ISUPCallReference; + addOptional: ISUPConnectionRequest; + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPNetworkSpecificFacility; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPINR [ + + + + ISUPINR class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgINR) + addFixed: ISUPInformationRequestIndicators; + addOptional: ISUPCallReference; + addOptional: ISUPNetworkSpecificFacility; + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPLPR [ + + + + ISUPLPR class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgLPR) + addOptional: ISUPMessageCompatibilityInformation; + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPCallTransferReference; + addOptional: ISUPLoopPreventionIndicators; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPNRM [ + + + + ISUPNRM class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgNRM) + addOptional: ISUPMessageCompatibilityInformation; + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPEchoControlInformation; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPPRI [ + + + + ISUPPRI class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgPRI) + addOptional: ISUPMessageCompatibilityInformation; + addOptional: ISUPParameterCompatibilityInformation; + addOptionals: ISUPOptionalForwardCallIndicators; + addOptionals: ISUPOptionalBackwardCallIndicators; + addOptional: ISUPApplicationTransportParameter; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPREL [ + + + + ISUPREL class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgREL) + addVariable: ISUPCauseIndicators; + addOptional: ISUPRedirectionInformation; + addOptional: ISUPRedirectionNumber; + addOptional: ISUPAccessTransport; + addOptional: ISUPSignallingPointCode; + addOptional: ISUPUserToUserInformation; + addOptional: ISUPAutomaticCongestionLevel; + addOptional: ISUPNetworkSpecificFacility; + addOptional: ISUPAccessDeliveryInformation; + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPUserToUserIndicators; + addOptional: ISUPDisplayInformation; + addOptional: ISUPRemoteOperations; + addOptional: ISUPHTRInformation; + addOptional: ISUPRedirectCounter; + addOptional: ISUPRedirectBackwardInformation; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPRES [ + + + + ISUPRES class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgRES) + addFixed: ISUPSuspendResumeIndicators; + addOptional: ISUPCallReference; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPRLC [ + + + + ISUPRLC class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgRLC) + addOptional: ISUPCauseIndicators; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPSAM [ + + + + ISUPSAM class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgSAM) + addVariable: ISUPSubsequentNumber; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPSAN [ + + + + ISUPSAN class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgSAN) + addOptional: ISUPSubsequentNumber; + addOptional: ISUPMessageCompatibilityInformation; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPSEG [ + + + + ISUPSEG class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgSEG) + addOptional: ISUPAccessTransport; + addOptional: ISUPUserToUserInformation; + addOptional: ISUPMessageCompatibilityInformation; + addOptionals: ISUPGenericDigits; + addOptionals: ISUPGenericNotificationIndicator; + addOptional: ISUPGenericNumber; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPUPT [ + + + + ISUPUPT class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgUPT) + addOptional: ISUPParameterCompatibilityInformation; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPMessage subclass: ISUPUSR [ + + + + ISUPUSR class >> tlvDescription [ + + ^ (self initWith: ISUPConstants msgUSR) + addVariable: ISUPUserToUserInformation; + addOptional: ISUPAccessTransport; + addOptional: ISUPEndOfOptionalParameters; + yourself. + ] +] + + +ISUPBLO subclass: ISUPBLA [ + + + + ISUPBLA class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgBLA; yourself + ] +] + + +ISUPBLO subclass: ISUPCCR [ + + + + ISUPCCR class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgCCR; yourself + ] +] + + +ISUPCGB subclass: ISUPCGBA [ + + + + ISUPCGBA class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgCGBA; yourself + ] +] + + +ISUPCGB subclass: ISUPCGUA [ + + + + ISUPCGUA class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgCGUA; yourself + ] +] + + +ISUPCGB subclass: ISUPCGU [ + + + + ISUPCGU class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgCGU; yourself + ] +] + + +ISUPFAA subclass: ISUPFAR [ + + + + ISUPFAR class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgFAR; yourself + ] +] + + +ISUPGRS subclass: ISUPGRA [ + + + + ISUPGRA class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgGRA; yourself + ] +] + + +ISUPBLO subclass: ISUPLPA [ + + + + ISUPLPA class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgLPA; yourself + ] +] + + +ISUPBLO subclass: ISUPOLM [ + + + + ISUPOLM class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgOLM; yourself + ] +] + + +ISUPBLO subclass: ISUPRSC [ + + + + ISUPRSC class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgRSC; yourself + ] +] + + +ISUPRES subclass: ISUPSUS [ + + + + ISUPSUS class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgSUS; yourself + ] +] + + +ISUPBLO subclass: ISUPUBA [ + + + + ISUPUBA class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgUBA; yourself + ] +] + + +ISUPBLO subclass: ISUPUBL [ + + + + ISUPUBL class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgUBL; yourself + ] +] + + +ISUPBLO subclass: ISUPUCIC [ + + + + ISUPUCIC class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgUCIC; yourself + ] +] + + +ISUPUPT subclass: ISUPUPA [ + + + + ISUPUPA class >> tlvDescription [ + + ^ (super tlvDescription) + type: ISUPConstants msgUPA; yourself + ] +] + diff --git a/osmo-st-network/m2ua/M2UAApplicationServerProcess.st b/osmo-st-network/m2ua/M2UAApplicationServerProcess.st new file mode 100644 index 0000000..e9fb1aa --- /dev/null +++ b/osmo-st-network/m2ua/M2UAApplicationServerProcess.st @@ -0,0 +1,507 @@ +" + (C) 2013 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: M2UAApplicationServerProcess [ + | socket asp_active_block asp_down_block asp_inactive_block asp_up_block error_block notify_block sctp_confirm_block sctp_released_block sctp_restarted_block sctp_status_block established state t_ack lastMsg on_state_change as_state | + + + + + M2UAApplicationServerProcess class >> initWith: aService [ + ^self new + socketService: aService; + yourself + ] + + M2UAApplicationServerProcess class >> new [ + ^super new + initialize; + yourself + ] + + onError: aBlock [ + "M-ERROR indication + Direction: M2UA -> LM + Purpose: ASP or SGP reports that it has received an ERROR + message from its peer." + + + error_block := aBlock + ] + + onNotify: aBlock [ + "M-NOTIFY indication + Direction: M2UA -> LM + Purpose: ASP reports that it has received a NOTIFY message + from its peer." + + + notify_block := aBlock + ] + + onSctpEstablished: aBlock [ + "M-SCTP_ESTABLISH confirm + Direction: M2UA -> LM + Purpose: ASP confirms to LM that it has established an SCTP association with an SGP." + + + sctp_confirm_block := aBlock + ] + + onSctpReleased: aBlock [ + "M-SCTP_RELEASE confirm + Direction: M2UA -> LM + Purpose: ASP confirms to LM that it has released SCTP association with SGP." + + + sctp_released_block := aBlock + ] + + onSctpRestarted: aBlock [ + "M-SCTP_RELEASE indication + Direction: M2UA -> LM + Purpose: SGP informs LM that ASP has released an SCTP association." + + + sctp_restarted_block := aBlock + ] + + onSctpStatus: aBlock [ + "M-SCTP_STATUS indication + Direction: M2UA -> LM + Purpose: M2UA reports status of SCTP association." + + + sctp_status_block := aBlock + ] + + sctpEstablish [ + "M-SCTP_ESTABLISH request + Direction: LM -> M2UA + Purpose: LM requests ASP to establish an SCTP association with an SGP." + + + established := false. + socket stop. + socket start + ] + + sctpRelease [ + "M-SCTP_RELEASE request + Direction: LM -> M2UA + Purpose: LM requests ASP to release an SCTP association with SGP." + + + established := false. + socket stop. + t_ack ifNotNil: [t_ack cancel] + ] + + sctpStatusRequest [ + "M-SCTP_STATUS request + Direction: LM -> M2UA + Purpose: LM requests M2UA to report status of SCTP association." + + + self notYetImplemented + ] + + aspActive [ + + "M-ASP_ACTIVE request + Direction: LM -> M2UA + Purpose: LM requests ASP to send an ASP ACTIVE message to the SGP." + + | msg | + self checkNextState: M2UAAspStateActive. + msg := M2UAMSG new + class: M2UAConstants clsASPTM; + msgType: M2UAConstants asptmActiv; + addTag: self createIdentIntTag; + addTag: self createInfoTag; + yourself. + self send: msg + ] + + aspDown [ + + "M-ASP_DOWN request + Direction: LM -> M2UA + Purpose: LM requests ASP to stop its operation and send an ASP DOWN + message to the SGP." + + | msg | + self checkNextState: M2UAAspStateDown. + msg := M2UAMSG new + class: M2UAConstants clsASPSM; + msgType: M2UAConstants aspsmDown; + addTag: self createAspIdentTag; + addTag: self createInfoTag; + yourself. + self send: msg + ] + + aspInactive [ + + "M-ASP_INACTIVE request + Direction: LM -> M2UA + Purpose: LM requests ASP to send an ASP INACTIVE message to the SGP." + + | msg | + self checkNextState: M2UAAspStateInactive. + msg := M2UAMSG new + class: M2UAConstants clsASPTM; + msgType: M2UAConstants asptmInactiv; + addTag: self createIdentIntTag; + addTag: self createInfoTag; + yourself. + self send: msg + ] + + aspUp [ + + "M-ASP_UP request + Direction: LM -> M2UA + Purpose: LM requests ASP to start its operation and send an ASP UP + message to the SGP." + + | msg | + self checkNextState: M2UAAspStateInactive. + msg := M2UAMSG new + class: M2UAConstants clsASPSM; + msgType: M2UAConstants aspsmUp; + addTag: self createAspIdentTag; + addTag: self createInfoTag; + yourself. + self send: msg + ] + + onAspActive: aBlock [ + "M-ASP_ACTIVE confirm + Direction: M2UA -> LM + Purpose: ASP reports that is has received an ASP ACTIVE + Acknowledgment message from the SGP." + + + asp_active_block := aBlock + ] + + onAspDown: aBlock [ + "M-ASP_DOWN confirm + Direction: M2UA -> LM + Purpose: ASP reports that is has received an ASP DOWN Acknowledgment + message from the SGP." + + + asp_down_block := aBlock + ] + + onAspInactive: aBlock [ + "M-ASP_INACTIVE confirm + Direction: M2UA -> LM + Purpose: ASP reports that is has received an ASP INACTIVE + Acknowledgment message from the SGP." + + + asp_inactive_block := aBlock + ] + + onAspUp: aBlock [ + "M-ASP_UP confirm + Direction: M2UA -> LM + Purpose: ASP reports that it has received an ASP UP Acknowledgment + message from the SGP." + + + asp_up_block := aBlock + ] + + onStateChange: aBlock [ + "A generic callback for all state changes" + + + on_state_change := aBlock + ] + + deregisterLinkKey [ + "M-LINK_KEY_DEREG Request + Direction: LM -> M2UA + Purpose: LM requests ASP to de-register Link Key with SG by sending + DEREG REQ message." + + + self notYetImplemented + ] + + onLinkKeyDeregistered: aBlock [ + "M-LINK_KEY_DEREG Confirm + Direction: M2UA -> LM + Purpose: ASP reports to LM that it has successfully received a + DEREG RSP message from SG." + + + self notYetImplemented + ] + + onLinkKeyRegistered: aBlock [ + "M-LINK_KEY_REG Confirm + Direction: M2UA -> LM + Purpose: ASP reports to LM that it has successfully received a REG + RSP message from SG." + + + self notYetImplemented + ] + + registerLinkKey [ + "M-LINK_KEY_REG Request + Direction: LM -> M2UA + Purpose: LM requests ASP to register Link Key with SG by sending REG + REQ message." + + + self notYetImplemented + ] + + hostname: aHostname port: aPort [ + "Select the SCTP hostname/port for the SG to connect to" + + + socket + hostname: aHostname; + port: aPort + ] + + createAspIdentTag [ + + ^M2UATag initWith: M2UAConstants tagAspIdent data: #(1 2 3 4) + ] + + createIdentIntTag [ + + ^M2UATag initWith: M2UAConstants tagIdentInt data: #(0 0 0 0) + ] + + createInfoTag [ + + ^M2UATag initWith: M2UAConstants tagInfo + data: 'Hello from Smalltalk' asByteArray + ] + + callNotification: aBlock [ + "Inform the generic method first, then all the others" + + + on_state_change ifNotNil: [on_state_change value]. + aBlock ifNotNil: [aBlock value] + ] + + checkNextState: nextState [ + "Check if nextState and state are compatible and if not + throw an exception. TODO:" + + + self state = nextState + ifTrue: + [^self error: ('M2UA ASP already in state <1p>' expandMacrosWith: state)]. + (self state nextPossibleStates includes: nextState) + ifFalse: + [^self error: ('M2UA ASP illegal state transition from <1p> to <2p>.' + expandMacrosWith: state + with: nextState)] + ] + + dispatchData: aByteArray [ + + | msg | + msg := M2UAMSG parseToClass: aByteArray. + msg dispatchOnAsp: self + ] + + dispatchNotification: aBlock [ + + aBlock value + ] + + internalReset [ + + self socketService: socket + ] + + moveToState: newState [ + + ((state nextPossibleStates includes: newState) or: [state = newState]) + ifFalse: + [^self error: ('M2UA ASP Illegal state transition from <1p> to <2p>' + expandMacrosWith: state + with: newState)]. + + "TODO: general on entry, on exit" + state := newState + ] + + sctpConnected [ + + "The connect was issued." + + | wasEstablished | + wasEstablished := established. + established := true. + state := M2UAAspStateDown. + t_ack ifNotNil: [t_ack cancel]. + wasEstablished = true + ifTrue: [sctp_confirm_block ifNotNil: [sctp_confirm_block value]] + ifFalse: [sctp_restarted_block ifNotNil: [sctp_restarted_block value]] + ] + + sctpReleased [ + "The SCTP connection has been released." + + + self moveToState: M2UAAspStateDown. + established = true ifFalse: [^self]. + sctp_released_block ifNotNil: [sctp_released_block value] + ] + + send: aMsg [ + "Forget about what we did before" + + + t_ack ifNotNil: [t_ack cancel]. + t_ack := TimerScheduler instance scheduleInSeconds: 2 + block: + ["Re-send the message" + + self logNotice: ('<1p>:<2p> Sending message has timed out' + expandMacrosWith: socket hostname + with: socket port) + area: #m2ua. + self send: aMsg]. + socket nextPut: aMsg toMessage asByteArray + ] + + initialize [ + + state := M2UAAspStateDown + ] + + socketService: aService [ + + socket := aService. + socket + onSctpConnect: [self sctpConnected]; + onSctpReleased: [self sctpReleased]; + onSctpData: + [:stream :assoc :ppid :data | + ppid = 2 + ifFalse: + [^self logNotice: 'M2UAApplicationServerProcess expecting PPID 2.' + area: #m2ua]. + self dispatchData: data] + ] + + handleAspActiveAck: aMsg [ + + t_ack cancel. + self moveToState: M2UAAspStateActive. + self callNotification: asp_active_block + ] + + handleAspDownAck: aMsg [ + + t_ack cancel. + as_state := nil. + self moveToState: M2UAAspStateDown. + self callNotification: asp_down_block + ] + + handleAspInactiveAck: aMsg [ + + t_ack cancel. + as_state := nil. + self moveToState: M2UAAspStateInactive. + self callNotification: asp_inactive_block + ] + + handleAspUpAck: aMsg [ + + t_ack cancel. + self moveToState: M2UAAspStateInactive. + self callNotification: asp_inactive_block + ] + + handleError: aMsg [ + "Cancel pending operations.. because something went wrong" + + + t_ack cancel. + error_block ifNotNil: [error_block value: aMsg] + ] + + handleNotify: aMsg [ + + "Extract the status" + + | tag type ident | + tag := aMsg findTag: M2UAConstants tagStatus. + tag ifNil: [^self]. + type := (tag data ushortAt: 1) swap16. + ident := (tag data ushortAt: 3) swap16. + type = M2UAConstants ntfyKindStateChange ifTrue: [as_state := ident]. + + "Inform our user about it" + notify_block ifNotNil: [notify_block value: type value: ident] + ] + + handleUnknownMessage: aMsg [ + "We got something we don't know. ignore it for now." + + + + ] + + isASActive [ + + ^as_state = M2UAConstants ntfyStateASActive + ] + + isASInactive [ + + ^as_state = M2UAConstants ntfyStateASInactive + ] + + isASPending [ + + ^as_state = M2UAConstants ntfyStateASPending + ] + + state [ + + ^state + ] +] diff --git a/osmo-st-network/m2ua/M2UAAspStateMachine.st b/osmo-st-network/m2ua/M2UAAspStateMachine.st new file mode 100644 index 0000000..0e495e6 --- /dev/null +++ b/osmo-st-network/m2ua/M2UAAspStateMachine.st @@ -0,0 +1,106 @@ +" + (C) 2013 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: M2UAAspStateMachine [ + | state | + + + + + M2UAAspStateMachine class >> initialState [ + ^M2UAAspStateDown + ] + + M2UAAspStateMachine class >> new [ + ^(self basicNew) + initialize; + yourself + ] + + entered: aState [ + aState entered + + "TODO notify users of the machine" + ] + + initialize [ + state := self class initialState on: self + ] + + left: aState [ + aState left + + "TODO notify users of the machine" + ] + + moveToState: aNewState [ + | oldState | + oldState := state. + state := (aNewState new) + machine: self; + yourself. + self left: oldState. + self entered: state + ] + + state [ + ^state class + ] + + aspActive: anEvent [ + + state onAspActive: anEvent + ] + + aspDown: anEvent [ + + state onAspDown: anEvent + ] + + aspInactive: anEvent [ + + state onAspInactive: anEvent + ] + + aspUp: anEvent [ + + state onAspUp: anEvent + ] + + otherAspInAsOverrides: anEvent [ + + state onOtherAspInAsOverrides: anEvent + ] + + sctpCdi: anEvent [ + + state onSctpCdi: anEvent + ] + + sctpRi: anEvent [ + + state onSctpRi: anEvent + ] +] diff --git a/osmo-st-network/m2ua/M2UAConstants.st b/osmo-st-network/m2ua/M2UAConstants.st new file mode 100644 index 0000000..8061c94 --- /dev/null +++ b/osmo-st-network/m2ua/M2UAConstants.st @@ -0,0 +1,126 @@ +" + (C) 2011-2013 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 . +" + +UAConstants subclass: M2UAConstants [ + + + + M2UAConstants class >> version [ ^ 1 ] + M2UAConstants class >> spare [ ^ 0 ] + + + M2UAConstants class >> tagData [ ^ 768 ] + M2UAConstants class >> tagDataTTC [ ^ 769 ] + M2UAConstants class >> tagStateReq [ ^ 770 ] + M2UAConstants class >> tagStateEvent [ ^ 771 ] + M2UAConstants class >> tagCongStatus [ ^ 772 ] + M2UAConstants class >> tagDiscStatus [ ^ 773 ] + M2UAConstants class >> tagAction [ ^ 774 ] + M2UAConstants class >> tagSeqNo [ ^ 775 ] + M2UAConstants class >> tagRetrRes [ ^ 776 ] + M2UAConstants class >> tagLinkKey [ ^ 777 ] + M2UAConstants class >> tagLocLinkeyIdent [ ^ 778 ] + M2UAConstants class >> tagSDT [ ^ 779 ] + M2UAConstants class >> tagSDL [ ^ 780 ] + M2UAConstants class >> tagRegRes [ ^ 781 ] + M2UAConstants class >> tagRegStatus [ ^ 782 ] + M2UAConstants class >> tagDeregRes [ ^ 783 ] + M2UAConstants class >> tagDeregStatus [ ^ 784 ] + + M2UAConstants class >> statusLpoSet [ ^ 0 ] + M2UAConstants class >> statusLpoClear [ ^ 1 ] + M2UAConstants class >> statusEmergSet [ ^ 2 ] + M2UAConstants class >> statusEmergClear [ ^ 3 ] + M2UAConstants class >> statusFlushBufs [ ^ 4 ] + M2UAConstants class >> statusContinue [ ^ 5 ] + M2UAConstants class >> statusClearRTB [ ^ 6 ] + M2UAConstants class >> statusAudit [ ^ 7 ] + M2UAConstants class >> statusCongCleared[ ^ 8 ] + M2UAConstants class >> statusCongAccept [ ^ 9 ] + M2UAConstants class >> statusCongDisc [ ^ 10 ] + + M2UAConstants class >> eventRPOEnter [ ^ 1 ] + M2UAConstants class >> eventRPOExit [ ^ 2 ] + M2UAConstants class >> eventLPOEnter [ ^ 3 ] + M2UAConstants class >> eventLPOExit [ ^ 4 ] + + M2UAConstants class >> congLevelNone [ ^ 0 ] + M2UAConstants class >> congLevel1 [ ^ 1 ] + M2UAConstants class >> congLevel2 [ ^ 2 ] + M2UAConstants class >> congLevel3 [ ^ 3 ] + + M2UAConstants class >> actionRtrvBSN [ ^ 0 ] + M2UAConstants class >> actionRtrvMSGs [ ^ 1 ] + + M2UAConstants class >> resultSuccess [ ^ 0 ] + M2UAConstants class >> resultFailure [ ^ 1 ] + + M2UAConstants class >> traOverride [ ^ 1 ] + M2UAConstants class >> traLoadShare [ ^ 2 ] + M2UAConstants class >> traBroadcast [ ^ 3 ] + + M2UAConstants class >> errInvalidVersion [ ^ 1 ] + M2UAConstants class >> errInvalidIdent [ ^ 2 ] + M2UAConstants class >> errUnsMsgClass [ ^ 3 ] + M2UAConstants class >> errUnsMsgType [ ^ 4 ] + M2UAConstants class >> errUnsTraMode [ ^ 5 ] + M2UAConstants class >> errUneMsg [ ^ 6 ] + M2UAConstants class >> errProtocolError [ ^ 7 ] + M2UAConstants class >> errUnsInterIdentInt [ ^ 8 ] + M2UAConstants class >> errInvalidStreamIdent[ ^ 9 ] + M2UAConstants class >> errUnsued1 [ ^ 10 ] + M2UAConstants class >> errUnsued2 [ ^ 11 ] + M2UAConstants class >> errUnsued3 [ ^ 12 ] + M2UAConstants class >> errRefused [ ^ 13 ] + M2UAConstants class >> errAspIdentRequired [ ^ 14 ] + M2UAConstants class >> errInvalidAspIdent [ ^ 15 ] + M2UAConstants class >> errAspActForIdent [ ^ 16 ] + M2UAConstants class >> errInvalidParamVal [ ^ 17 ] + M2UAConstants class >> errParamFieldError [ ^ 18 ] + M2UAConstants class >> errUnexpParam [ ^ 19 ] + M2UAConstants class >> errUnused4 [ ^ 20 ] + M2UAConstants class >> errUnused5 [ ^ 21 ] + M2UAConstants class >> errMissingParam [ ^ 22 ] + + M2UAConstants class >> ntfyKindStateChange [ ^ 1 ] + M2UAConstants class >> ntfyKindOther [ ^ 2 ] + + M2UAConstants class >> ntfyStateASInactive [ ^ 2 ] + M2UAConstants class >> ntfyStateASActive [ ^ 3 ] + M2UAConstants class >> ntfyStateASPending [ ^ 4 ] + + M2UAConstants class >> ntfyOtherInsuffRes [ ^ 1 ] + M2UAConstants class >> ntfyOtherAltAspActiv [ ^ 2 ] + M2UAConstants class >> ntfyOtherAspFailure [ ^ 3 ] + + M2UAConstants class >> regSuccess [ ^ 0 ] + M2UAConstants class >> regErrorUnknown [ ^ 1 ] + M2UAConstants class >> regErrorInvSDLI [ ^ 2 ] + M2UAConstants class >> regErrorInvSDTI [ ^ 3 ] + M2UAConstants class >> regErrorInvLinkKey [ ^ 4 ] + M2UAConstants class >> regErrorPermDenied [ ^ 5 ] + M2UAConstants class >> regErrorOverlapKey [ ^ 6 ] + M2UAConstants class >> regErrorNotProvisioned [ ^ 7 ] + M2UAConstants class >> regErrorInsuffRes [ ^ 8 ] + + M2UAConstants class >> deregSuccess [ ^ 0 ] + M2UAConstants class >> deregErrorUnknown [ ^ 1 ] + M2UAConstants class >> deregErrorInvIdent [ ^ 2 ] + M2UAConstants class >> deregErrorPermDenied [ ^ 3 ] + M2UAConstants class >> deregErrorNotReg [ ^ 4 ] +] diff --git a/osmo-st-network/m2ua/M2UAExamples.st b/osmo-st-network/m2ua/M2UAExamples.st new file mode 100644 index 0000000..feb29c4 --- /dev/null +++ b/osmo-st-network/m2ua/M2UAExamples.st @@ -0,0 +1,42 @@ +" + (C) 2013 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: M2UAExamples [ + + + + + createAsp [ + "Create a SCTP network service" + + | service asp manager | + service := SCTPNetworkService new + hostname: 'localhost'; + port: 2904; + yourself. + "Create the ASP" + asp := M2UAApplicationServerProcess initWith: service. + + "Create a Layer Management (LM) and start it" + manager := M2UALayerManagement new + applicationServerProcess: asp; + targetState: M2UAAspStateActive; + yourself. + manager manage + ] +] diff --git a/osmo-st-network/m2ua/M2UALayerManagement.st b/osmo-st-network/m2ua/M2UALayerManagement.st new file mode 100644 index 0000000..2f0e086 --- /dev/null +++ b/osmo-st-network/m2ua/M2UALayerManagement.st @@ -0,0 +1,127 @@ +" + (C) 2013 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: M2UALayerManagement [ + | targetState managedProcess | + + + + + applicationServerProcess: aProcess [ + + managedProcess := aProcess. + managedProcess + onSctpEstablished: [self sctpEstablished]; + onSctpRestarted: [self sctpEstablished]; + onError: [:msg | self m2uaError: msg]; + onNotify: [:type :ident | self m2uaNotify: type ident: ident]; + onAspActive: [self m2uaActive]; + onAspInactive: [self m2uaInactive]; + onAspDown: [self m2uaDown]; + onAspUp: [self m2uaUp] + ] + + manage [ + "I begin to manage the process." + + + managedProcess + sctpRelease; + sctpEstablish + ] + + targetState: aState [ + "Use the M2UAAspState subclasses for the states" + + + targetState := aState + ] + + applicationServerProcess [ + + ^managedProcess + ] + + m2uaActive [ + "E.g if the target state is already reached" + + + managedProcess state = targetState ifTrue: [^self targetReached]. + targetState = M2UAAspStateInactive + ifTrue: [managedProcess aspInactive] + ifFalse: [managedProcess aspDown] + ] + + m2uaDown [ + "E.g if the target state is already reached" + + + managedProcess state = targetState ifTrue: [^self targetReached]. + + "There is only one way forward" + managedProcess aspUp + ] + + m2uaError: aMsg [ + + self logNotice: 'M2UA Error.' area: #m2ua + ] + + m2uaInactive [ + "E.g if the target state is already reached" + + + managedProcess state = targetState ifTrue: [^self targetReached]. + targetState = M2UAAspStateActive + ifTrue: [managedProcess aspActive] + ifFalse: [managedProcess aspDown] + ] + + m2uaNotify: type ident: ident [ + "TODO: Check the type/ident" + + + + ] + + m2uaUp [ + "E.g if the target state is already reached" + + + managedProcess state = targetState ifTrue: [^self targetReached]. + targetState = M2UAAspStateActive + ifTrue: [managedProcess aspActive] + ifFalse: [managedProcess aspInactive] + ] + + sctpEstablished [ + "E.g if the target state is already reached" + + + managedProcess state = targetState ifTrue: [^self]. + "There is only one way forward" + managedProcess aspUp + ] + + targetReached [ + + ] +] diff --git a/osmo-st-network/m2ua/M2UAMSG.st b/osmo-st-network/m2ua/M2UAMSG.st new file mode 100644 index 0000000..1092229 --- /dev/null +++ b/osmo-st-network/m2ua/M2UAMSG.st @@ -0,0 +1,233 @@ +" + (C) 2011-2013 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: M2UAMSG [ + | msg_class msg_type tags | + + + + + M2UAMSG class >> parseFrom: aMsg [ + + self logDataContext: aMsg area: #m2ua. + + ^ self new + parseFrom: aMsg readStream; + yourself. + ] + + M2UAMSG class >> fromClass: aClass type: aType [ + + ^ self new + instVarNamed: #msg_class put: aClass; + instVarNamed: #msg_type put: aType; + yourself. + ] + + M2UAMSG class >> copyFromOtherMessage: aMsg [ + + ^ self new + msgClass: aMsg msgClass; + msgType: aMsg msgType; + tags: aMsg tags; + yourself + ] + + M2UAMSG class >> parseToClass: aMsg [ + + "This will attempt to parse the message into one of the + available subclasses." + + | rawMsg msgClasses | + rawMsg := self parseFrom: aMsg. + + "A simple class based lookup" + msgClasses := + {M2UAASPSMMessage. + M2UAASPTMMessage. + M2UAASPMGMTMessage}. + msgClasses do: + [:msgClass | + rawMsg msgClass = msgClass messageClass + ifTrue: + [msgClass allSubclassesDo: [:class | + class messageTag = rawMsg msgType + ifTrue: [^class copyFromOtherMessage: rawMsg]]]]. + + ^self error: ('Unknown message class (<1p>) or message type (<2p>)' + expandMacrosWith: rawMsg msgClass + with: rawMsg msgType) + ] + + msgClass [ + + ^ msg_class + ] + + msgType [ + + ^ msg_type + ] + + findTag: aTag [ + "I find a tag with a tag identifier" + + + ^self findTag: aTag ifAbsent: [nil] + ] + + findTag: aTag ifAbsent: aBlock [ + "I find a tag with a tag identifier" + + self tags do: [:each | + (each isTag: aTag) ifTrue: [ + ^ each + ] + ]. + + ^ aBlock value + ] + + tags [ + + ^ tags ifNil: [tags := OrderedCollection new] + ] + + parseFrom: aStream [ + + | len | + self parseVersion: aStream. + self parseSpare: aStream. + msg_class := aStream next. + msg_type := aStream next. + len := self parseLength: aStream. + tags := self parseTags: aStream to: aStream position + len - 8 + ] + + parseLength: aStream [ + + | len | + len := ((aStream next: 4) uintAt: 1) swap32. + aStream size - aStream position < (len - 8) + ifTrue: + [self + logError: ('M2UA length is not plausible <1p> <2p>.' expandMacrosWith: len + with: aStream size - aStream position) + area: #m2ua. + self + error: ('M2UA length is not plausible <1p> <2p>.' expandMacrosWith: len + with: aStream size - aStream position)]. + ^len + ] + + parseSpare: aStream [ + + | spare | + spare := aStream next. + spare = M2UAConstants spare + ifFalse: + [self logError: ('M2UA spare is wrong <1p>.' expandMacrosWith: spare) + area: #m2ua. + self error: ('M2UA spare is wrong <1p>.' expandMacrosWith: spare)] + ] + + parseTags: aStream to: end [ + + tags := OrderedCollection new. + [aStream position < end] + whileTrue: [tags add: (M2UATag fromStream: aStream)]. + ^tags + ] + + parseVersion: aStream [ + + | version | + version := aStream next. + version = M2UAConstants version + ifFalse: + [self logError: ('M2UA version is wrong <1p>.' expandMacrosWith: version) + area: #m2ua. + self error: ('M2UA version is wrong <1p>.' expandMacrosWith: version)] + ] + addTag: aTag [ + + self tags add: aTag. + ] + + writeOn: aMsg [ + | tag_data | + + + "Create the tag data" + tag_data := MessageBuffer new. + self tags do: [:each | + each writeOn: tag_data + ]. + + aMsg putByte: M2UAConstants version. + aMsg putByte: M2UAConstants spare. + aMsg putByte: msg_class. + aMsg putByte: msg_type. + aMsg putLen32: tag_data size + 8. + aMsg putByteArray: tag_data. + ] + + class: aClass [ + + msg_class := aClass + ] + + msgClass: aClass [ + + self class: aClass + ] + + msgType: aType [ + + msg_type := aType + ] + + tags: aTags [ + + tags := aTags + ] + + dispatchOnAsp: anAsp [ + + anAsp handleUnknownMessage: self + ] +] + diff --git a/osmo-st-network/m2ua/M2UAMessages.st b/osmo-st-network/m2ua/M2UAMessages.st new file mode 100644 index 0000000..e9f4a16 --- /dev/null +++ b/osmo-st-network/m2ua/M2UAMessages.st @@ -0,0 +1,217 @@ +" + (C) 2011-2013 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 . +" + +M2UAMSG subclass: M2UAASPSMMessage [ + + + + + M2UAASPSMMessage class >> messageClass [ + ^M2UAConstants clsASPSM + ] +] + +M2UAMSG subclass: M2UAASPTMMessage [ + + + + + M2UAASPTMMessage class >> messageClass [ + ^M2UAConstants clsASPTM + ] +] + +M2UAMSG subclass: M2UAASPMGMTMessage [ + + + + + M2UAASPMGMTMessage class >> messageClass [ + ^M2UAConstants clsMgmt + ] +] + +M2UAASPSMMessage subclass: M2UAApplicationServerProcessHeartbeatAck [ + + + + + M2UAApplicationServerProcessHeartbeatAck class >> messageTag [ + ^M2UAConstants aspsmBeatAck + ] +] + +M2UAASPSMMessage subclass: M2UAApplicationServerProcessDown [ + + + + + M2UAApplicationServerProcessDown class >> messageTag [ + ^M2UAConstants aspsmDown + ] + + dispatchOnAsp: anAsp [ + + anAsp handleAspDown: self + ] +] + +M2UAASPSMMessage subclass: M2UAApplicationServerProcessHeartbeat [ + + + + + M2UAApplicationServerProcessHeartbeat class >> messageTag [ + ^M2UAConstants aspsmBeat + ] +] + +M2UAASPSMMessage subclass: M2UAApplicationServerProcessDownAck [ + + + + + M2UAApplicationServerProcessDownAck class >> messageTag [ + ^M2UAConstants aspsmDownAck + ] + + dispatchOnAsp: anAsp [ + + anAsp handleAspDownAck: self + ] +] + +M2UAASPSMMessage subclass: M2UAApplicationServerProcessUp [ + + + + + M2UAApplicationServerProcessUp class >> messageTag [ + ^M2UAConstants aspsmUp + ] + + dispatchOnAsp: anAsp [ + + anAsp handleAspUp: self + ] +] + +M2UAASPTMMessage subclass: M2UAApplicationServerProcessInactiveAck [ + + + + + M2UAApplicationServerProcessInactiveAck class >> messageTag [ + ^M2UAConstants asptmInactivAck + ] + + dispatchOnAsp: anAsp [ + + anAsp handleAspInactiveAck: self + ] +] + +M2UAASPTMMessage subclass: M2UAApplicationServerProcessActive [ + + + + + M2UAApplicationServerProcessActive class >> messageTag [ + ^M2UAConstants asptmActiv + ] + + dispatchOnAsp: anAsp [ + + anAsp handleAspActive: self + ] +] + +M2UAASPTMMessage subclass: M2UAApplicationServerProcessInactive [ + + + + + M2UAApplicationServerProcessInactive class >> messageTag [ + ^M2UAConstants asptmInactiv + ] + + dispatchOnAsp: anAsp [ + + anAsp handleAspInactive: self + ] +] + +M2UAASPMGMTMessage subclass: M2UAApplicationServerProcessNotify [ + + + + + M2UAApplicationServerProcessNotify class >> messageTag [ + ^M2UAConstants mgmtNtfy + ] + + dispatchOnAsp: anAsp [ + + anAsp handleNotify: self + ] +] + +M2UAASPMGMTMessage subclass: M2UAApplicationServerProcessError [ + + + + + M2UAApplicationServerProcessError class >> messageTag [ + ^M2UAConstants mgmtError + ] + + dispatchOnAsp: anAsp [ + + anAsp handleError: self + ] +] + +M2UAASPTMMessage subclass: M2UAApplicationServerProcessActiveAck [ + + + + + M2UAApplicationServerProcessActiveAck class >> messageTag [ + ^M2UAConstants asptmActivAck + ] + + dispatchOnAsp: anAsp [ + + anAsp handleAspActiveAck: self + ] +] + +M2UAASPSMMessage subclass: M2UAApplicationServerProcessUpAck [ + + + + + M2UAApplicationServerProcessUpAck class >> messageTag [ + ^M2UAConstants aspsmUpAck + ] + + dispatchOnAsp: anAsp [ + + anAsp handleAspUpAck: self + ] +] diff --git a/osmo-st-network/m2ua/M2UAStates.st b/osmo-st-network/m2ua/M2UAStates.st new file mode 100644 index 0000000..dc26c85 --- /dev/null +++ b/osmo-st-network/m2ua/M2UAStates.st @@ -0,0 +1,298 @@ +" + (C) 2013 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 . +" + +STInST.RBProgramNodeVisitor subclass: M2UAStateMachineVisitor [ + | states | + + + + + acceptMessageNode: aNode [ + aNode selector = #moveToState: + ifTrue: [self addTransition: aNode arguments first name asString]. + super acceptMessageNode: aNode + ] + + addTransition: aStateName [ + + self stateSet add: aStateName + ] + + stateSet [ + + ^states ifNil: [states := Set new] + ] +] + + + +Object subclass: M2UAStateBase [ + | machine | + + + + + M2UAStateBase class >> addStateFrom: aMethod to: newState class: aClass on: aStream [ + aStream + nextPutAll: aClass name asString; + nextPutAll: ' -> '; + nextPutAll: newState; + nextPutAll: ' [ label = "'; + nextPutAll: aMethod asString allButLast; + nextPutAll: '"];'; + nl. + ] + + M2UAStateBase class >> generateGraphviz [ + | stream | + stream := WriteStream on: String new. + stream + nextPutAll: 'digraph {'; + nl. + self subclassesDo: + [:class | + class selectors do: [:selector | + | codeVisitor method | + method := class >> selector. + codeVisitor := (STInST.RBBracketedMethodParser + parseMethod: method methodSourceString) body + acceptVisitor: M2UAStateMachineVisitor new. + codeVisitor stateSet do: + [:newState | + self + addStateFrom: method selector asString + to: newState + class: class + on: stream]]]. + ^stream + nextPutAll: '}'; + contents + ] + + M2UAStateBase class >> on: aMachine [ + "Create a new state for a machine" + + ^self new + machine: aMachine; + yourself + ] + + entered [ + "The state has been entered" + ] + + left [ + "The state has been left" + ] + + machine: aMachine [ + machine := aMachine + ] + + moveToState: aNewState [ + + machine moveToState: aNewState + ] +] + + + +M2UAStateBase subclass: M2UAAsState [ + + + +] + + + +M2UAAsState subclass: M2UAAsStateInactive [ + + + + + onAllAspDown: anEvent [ + "All ASP trans to ASP-DOWN" + + + self moveToState: M2UAAsStateDown + ] + + onAspActive: anEvent [ + "one ASP trans to ACTIVE" + + + self moveToState: M2UAAsStateActive + ] +] + + + +M2UAAsState subclass: M2UAAsStatePending [ + + + + + onAspUp: anEvent [ + "One ASP trans to ASP-ACTIVE" + + + self stopTr. + self moveToState: M2UAAsStateActive + ] + + onTrExpiry [ + "Tr Expiry, at least one ASP in ASP-INACTIVE -> AS-INACTIVE" + + "Tr Expiry and no ASPin ASP-INACTIVE state" + + + self hasInactiveAsp + ifTrue: [self moveToState: M2UAAsStateInactive] + ifFalse: [self moveToState: M2UAAsStateDown] + ] +] + + + +M2UAStateBase subclass: M2UAAspState [ + + + + + M2UAAspState class >> nextPossibleStates [ + ^self subclassResponsibility + ] +] + + + +M2UAAspState subclass: M2UAAspStateActive [ + + + + + M2UAAspStateActive class >> nextPossibleStates [ + ^ {M2UAAspStateInactive. M2UAAspStateDown} + ] + + onAspDown: anEvent [ + + self moveToState: M2UAAspStateDown + ] + + onAspInactive: anEvent [ + + ^self moveToState: M2UAAspStateInactive + ] + + onOtherAspInAsOverrides: anEvent [ + + ^self moveToState: M2UAAspStateInactive + ] + + onSctpCdi: anEvent [ + + self moveToState: M2UAAspStateDown + ] + + onSctpRi: anEvent [ + + ^self moveToState: M2UAAspStateDown + ] +] + + + +M2UAAspState subclass: M2UAAspStateDown [ + + + + + M2UAAspStateDown class >> nextPossibleStates [ + ^{M2UAAspStateInactive} + ] + + onAspUp: anEvent [ + + ^self moveToState: M2UAAspStateInactive + ] +] + + + +M2UAAspState subclass: M2UAAspStateInactive [ + + + + + M2UAAspStateInactive class >> nextPossibleStates [ + ^ {M2UAAspStateActive. M2UAAspStateDown} + ] + + onAspActive: anEvent [ + + ^self moveToState: M2UAAspStateActive + ] + + onAspDown: anEvent [ + + ^self moveToState: M2UAAspStateDown + ] + + onSctpCdi: anEvent [ + + ^self moveToState: M2UAAspStateDown + ] + + onSctpRi: anEvent [ + + ^self moveToState: M2UAAspStateDown + ] +] + + + +M2UAAsState subclass: M2UAAsStateDown [ + + + + + onAspInactive: anEvent [ + "One ASP trans to ASP-INACTIVE" + + + self movesToState: M2UAAsStateInactive + ] +] + + + +M2UAAsState subclass: M2UAAsStateActive [ + + + + + onLastActiveAspDown: anEvent [ + "Last ACTIVEASP trans to ASP-INACTIVE or ASP-Down" + + + self startTr. + self moveToState: M2UAAsStatePending + ] +] + diff --git a/osmo-st-network/m2ua/M2UATag.st b/osmo-st-network/m2ua/M2UATag.st new file mode 100644 index 0000000..3f42563 --- /dev/null +++ b/osmo-st-network/m2ua/M2UATag.st @@ -0,0 +1,85 @@ +" + (C) 2011-2013 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: M2UATag [ + | tag_nr data | + + + + + M2UATag class >> fromStream: aStream [ + + ^ self new + parseFrom: aStream + ] + + M2UATag class >> initWith: aTag data: aData [ + + ^ self new + instVarNamed: #tag_nr put: aTag; + instVarNamed: #data put: aData; + yourself + ] + + parseFrom: aStream [ + | len padding | + + + tag_nr := ((aStream next: 2) shortAt: 1) swap16. + len := ((aStream next: 2) shortAt: 1) swap16. + data := aStream next: len - 4. + + padding := len \\ 4. + padding > 0 ifTrue: [ + self logNotice: + ('Going to skip <1p> bytes' expandMacrosWith: 4 - padding) area: #m2ua. + aStream skip: 4 - padding. + ]. + ] + + nr [ + + ^ tag_nr + ] + + data [ + + ^ data ifNil: [data := ByteArray new] + ] + + writeOn: aMsg [ + | rest | + + + aMsg putLen16: tag_nr. + aMsg putLen16: self data size + 4. + aMsg putByteArray: self data. + + rest := self data size \\ 4. + rest > 0 ifTrue: [ + aMsg putByteArray: (ByteArray new: 4 - rest). + ]. + ] + + isTag: aNr [ + + ^ self nr = aNr + ] +] + diff --git a/osmo-st-network/m2ua/M2UATerminology.st b/osmo-st-network/m2ua/M2UATerminology.st new file mode 100644 index 0000000..6c1ae72 --- /dev/null +++ b/osmo-st-network/m2ua/M2UATerminology.st @@ -0,0 +1,44 @@ +" + (C) 2011-2013 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: M2UATerminology [ + + + +] diff --git a/osmo-st-network/m2ua/M2UATests.st b/osmo-st-network/m2ua/M2UATests.st new file mode 100644 index 0000000..4f6def2 --- /dev/null +++ b/osmo-st-network/m2ua/M2UATests.st @@ -0,0 +1,222 @@ +" + (C) 2013 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: M2UAASMock [ + | socket | + + + + + socketService: aSocket [ + + socket := aSocket + ] + + handleAspActive: aMsg [ + + | ret | + ret := M2UAMSG new + msgClass: M2UAConstants clsASPTM; + msgType: M2UAConstants asptmActivAck; + yourself. + socket sendToAsp: ret toMessage asByteArray + ] + + handleAspDown: aMsg [ + + | ret | + ret := M2UAMSG new + msgClass: M2UAConstants clsASPSM; + msgType: M2UAConstants aspsmDownAck; + yourself. + socket sendToAsp: ret toMessage asByteArray + ] + + handleAspInactive: aMsg [ + + | ret | + ret := M2UAMSG new + msgClass: M2UAConstants clsASPTM; + msgType: M2UAConstants asptmInactivAck; + yourself. + socket sendToAsp: ret toMessage asByteArray + ] + + handleAspUp: aMsg [ + + | ret | + ret := M2UAMSG new + msgClass: M2UAConstants clsASPSM; + msgType: M2UAConstants aspsmUpAck; + yourself. + socket sendToAsp: ret toMessage asByteArray + ] + + onData: aData [ + | msg | + msg := M2UAMSG parseToClass: aData. + msg dispatchOnAsp: self + ] +] + +Object subclass: SCTPNetworkServiceMock [ + | on_connect on_released on_data as asp | + + + + + onSctpConnect: aBlock [ + + on_connect := aBlock + ] + + applicationServer: anAs [ + + as := anAs + ] + + applicationServerProcess: anAsp [ + + asp := anAsp + ] + + onSctpData: aBlock [ + + on_data := aBlock + ] + + onSctpReleased: aBlock [ + + on_released := aBlock + ] + + hostname [ + + ^'localhost' + ] + + port [ + + ^0 + ] + + start [ + "Nothing" + + + on_connect value + ] + + stop [ + + on_released value + ] + + nextPut: aMsg [ + as onData: aMsg + ] + + sendToAsp: aMsg [ + on_data + value: nil + value: nil + value: 2 + value: aMsg + ] +] + +TestCase subclass: M2UAApplicationServerProcessTest [ + + + + + testCreation [ + | asp | + asp := M2UAApplicationServerProcess new + onAspActive: []; + onAspDown: []; + onAspInactive: []; + onAspUp: []; + onStateChange: []; + onError: [:msg | ]; + onNotify: [:type :ident | ]; + onSctpEstablished: []; + onSctpReleased: []; + onSctpRestarted: []; + onSctpStatus: []; + yourself + ] + + testStateTransitions [ + | mock as asp | + mock := SCTPNetworkServiceMock new. + as := M2UAASMock new + socketService: mock; + yourself. + asp := M2UAApplicationServerProcess initWith: mock. + mock + applicationServer: as; + applicationServerProcess: asp. + + "This works as the mock will handle this synchronously" + self assert: asp state = M2UAAspStateDown. + asp + sctpEstablish; + aspUp. + self assert: asp state = M2UAAspStateInactive. + + "Now bring it down and up again" + asp aspDown. + self assert: asp state = M2UAAspStateDown. + asp + aspUp; + aspActive. + self assert: asp state = M2UAAspStateActive. + asp aspDown. + self assert: asp state = M2UAAspStateDown. + asp + aspUp; + aspActive; + aspInactive. + self assert: asp state = M2UAAspStateInactive. + asp sctpRelease. + self assert: asp state = M2UAAspStateDown + ] +] + +TestCase subclass: M2UAAspStateMachineTest [ + + + + + testLegalTransitions [ + | machine | + machine := M2UAAspStateMachine new. + self assert: machine state = M2UAAspStateDown. + machine aspUp: 'Link is up'. + self assert: machine state = M2UAAspStateInactive. + machine aspActive: 'Active'. + self assert: machine state = M2UAAspStateActive. + machine aspInactive: 'Inactive'. + self assert: machine state = M2UAAspStateInactive. + machine aspActive: 'Active'. + self assert: machine state = M2UAAspStateActive. + machine sctpCdi: 'Connection is gone'. + self assert: machine state = M2UAAspStateDown + ] +] diff --git a/osmo-st-network/mtp3/MTP3Messages.st b/osmo-st-network/mtp3/MTP3Messages.st new file mode 100644 index 0000000..d16b36e --- /dev/null +++ b/osmo-st-network/mtp3/MTP3Messages.st @@ -0,0 +1,1435 @@ +" + (C) 2013 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: MTP3Address [ + | dpc opc | + + + +] + + + +Object subclass: MTP3Service [ + | on_transfer on_pause on_resume on_status | + + + + + transfer: aByteArray to: anAddr [ + + ^self notYetImplemented + ] + + onPause: aBlock [ + "Called with DPC" + + + on_pause := aBlock + ] + + onResume: aBlock [ + "Called with affected DPC" + + + on_resume := aBlock + ] + + onStatus: aBlock [ + "Called with the Affected DPC" + + + on_status := aBlock + ] + + onTransfer: aBlock [ + "Called with MTP3Address and UserData" + + + on_transfer := aBlock + ] +] + + + +Object subclass: MTP3NetworkManagementTimer [ + + + + + MTP3NetworkManagementTimer class >> T1 [ + "Delay to avoid message mis-sequencing on changeover." + + + ^500 to: 1200 + ] + + MTP3NetworkManagementTimer class >> T10 [ + "Waiting to repeat signalling route set test message. + The maximum value may be extended at the discretion of the management function in + certain situations, e.g. many signalling points being unavailable or signalling point of + known long term unavailability." + + + ^30000 to: 60000 + ] + + MTP3NetworkManagementTimer class >> T11 [ + "Transfer restricted timer. (This is one way of implementing the function described in + 13.4 and mainly intended to simplify STPs.)" + + + ^30000 to: 90000 + ] + + MTP3NetworkManagementTimer class >> T12 [ + "Waiting for uninhibit acknowledgement." + + + ^800 to: 1500 + ] + + MTP3NetworkManagementTimer class >> T13 [ + "Waiting for force uninhibit." + + + ^800 to: 1500 + ] + + MTP3NetworkManagementTimer class >> T14 [ + "Waiting for inhibition acknowledgement." + + + ^2000 to: 3000 + ] + + MTP3NetworkManagementTimer class >> T15 [ + "Waiting to start signalling route set congestion test." + + + ^2000 to: 3000 + ] + + MTP3NetworkManagementTimer class >> T16 [ + "Waiting for route set congestion status update." + + + ^1400 to: 2000 + ] + + MTP3NetworkManagementTimer class >> T17 [ + "Delay to avoid oscillation of initial alignment failure and link restart." + + + ^800 to: 1500 + ] + + MTP3NetworkManagementTimer class >> T18 [ + "Timer8 within a signalling point whose MTP restarts for supervising link and link set + activation as well as the receipt of routing information. + The value is implementation and network dependent. + Criteria to choose T18 are given in 9.2." + + + ^self notYetImplemented + ] + + MTP3NetworkManagementTimer class >> T19 [ + "Supervision timer during MTP restart to avoid possible ping-pong of TFP, TFR1 and + TRA messages." + + + ^67000 to: 69000 + ] + + MTP3NetworkManagementTimer class >> T2 [ + "Waiting for changeover acknowledgement." + + + ^700 to: 2000 + ] + + MTP3NetworkManagementTimer class >> T20 [ + "Overall MTP restart timer at the signalling point whose MTP restarts." + + + ^59000 to: 61000 + ] + + MTP3NetworkManagementTimer class >> T21 [ + "Overall MTP restart timer at a signalling point adjacent to one whose MTP restarts." + + + ^63000 to: 65000 + ] + + MTP3NetworkManagementTimer class >> T22 [ + "Local inhibit test timer." + + + ^3 * 60 * 1000 to: 6 * 60 * 1000 + ] + + MTP3NetworkManagementTimer class >> T23 [ + "Remote inhibit test timer." + + + ^3 * 60 * 1000 to: 6 * 60 * 1000 + ] + + MTP3NetworkManagementTimer class >> T24 [ + "Stabilising timer after removal of local processor outage, used in LPO latching to RPO + (national option)." + + + ^500 to: 500 + ] + + MTP3NetworkManagementTimer class >> T3 [ + "Time controlled diversion-delay to avoid mis-sequencing on changeback." + + + ^500 to: 1200 + ] + + MTP3NetworkManagementTimer class >> T4 [ + "Waiting for changeback acknowledgement (first attempt)." + + + ^500 to: 1200 + ] + + MTP3NetworkManagementTimer class >> T5 [ + "Waiting for changeback acknowledgement (second attempt)." + + + ^500 to: 1200 + ] + + MTP3NetworkManagementTimer class >> T6 [ + "Delay to avoid message mis-sequencing on controlled rerouting." + + + ^500 to: 1200 + ] + + MTP3NetworkManagementTimer class >> T7 [ + "Waiting for signalling data link connection acknowledgement." + + + ^1000 to: 2000 + ] + + MTP3NetworkManagementTimer class >> T8 [ + "Transfer prohibited inhibition timer (transient solution)." + + + ^800 to: 1200 + ] + + MTP3NetworkManagementTimer class >> T9 [ + + ^self shouldNotImplement + ] +] + + + +Object subclass: MTP3Field [ + + + +] + + + +MTP3Field subclass: MTP3Heading [ + | h0 h1 | + + + + + MTP3Heading class >> parseFrom: aStream [ + | byte | + byte := aStream next. + ^(self new) + h0: (byte bitAnd: 2r1111); + h1: (byte bitShift: -4); + yourself + ] + + h0: aHeading [ + + h0 := aHeading + ] + + h1: aHeading [ + + h1 := aHeading + ] + + h0 [ + + ^h0 + ] + + h1 [ + + ^h1 + ] + + writeOn: aBuffer [ + + | byte | + byte := h0 bitOr: (h1 bitShift: 4). + aBuffer putByte: byte + ] +] + + + +Object subclass: MTP3LinkTestTimer [ + + + + + T1 [ + "Supervision timer for signalling link test + acknowledgement message. Equal or greater than T6 of Q.703" + + ^4 * 1000 to: 12 * 1000 + ] + + T2 [ + "Interval timer for sending signalling link + test messages" + + ^30 * 1000 to: 90 * 1000 + ] +] + + + +Object subclass: MTP3MSG [ + | service label heading | + + + + + MTP3MSG class >> findMessageClassFor: aServiceIndicator heading: aHeading [ + + self subclassesDo: + [:each | + (each isServiceCompatible: aServiceIndicator) + ifTrue: [^each findClassForHeading: aHeading]]. + ^nil + ] + + MTP3MSG class >> parseFrom: aStream [ + + | service label heading msg | + service := MTP3ServiceIndicators parseFrom: aStream. + label := MTP3Label parseFrom: aStream. + heading := MTP3Heading parseFrom: aStream. + msg := ((self findMessageClassFor: service heading: heading) new) + service: service; + label: label; + heading: heading; + parseFrom: aStream; + yourself. + ^msg + ] + + heading: aHeading [ + + heading := aHeading + ] + + label: aLabel [ + + label := aLabel + ] + + service: aService [ + + service := aService + ] + + writeOn: aBuffer [ + + service writeOn: aBuffer. + label writeOn: aBuffer. + heading writeOn: aBuffer + ] +] + + + +MTP3MSG subclass: MTP3LinkTestMSG [ + | pattern | + + + + + MTP3LinkTestMSG class >> h0 [ + ^2r0001 + ] + + MTP3LinkTestMSG class >> h1SLTA [ + ^2r0010 + ] + + MTP3LinkTestMSG class >> h1SLTM [ + ^2r0001 + ] + + MTP3LinkTestMSG class >> findClassForHeading: aHeading [ + + aHeading h0 = self h0 ifFalse: [^self error: 'Wrong heading']. + self subclassesDo: [:each | each h1 = aHeading h1 ifTrue: [^each]] + ] + + MTP3LinkTestMSG class >> isServiceCompatible: aServiceIndicator [ + + ^aServiceIndicator serviceIndicator + = MTP3ServiceIndicators signallingNetworkTestingAndMaintenance + ] + + writeOn: aBuffer [ + + | len | + super writeOn: aBuffer. + len := (pattern size bitShift: 4) bitAnd: 2r11110000. + aBuffer putByte: len. + aBuffer putByteArray: pattern + ] + + parseFrom: aStream [ + + | length | + length := aStream next bitShift: -4. + self testPattern: (aStream next: length) + ] + + testPattern [ + + ^pattern + ] + + testPattern: aPattern [ + + pattern := aPattern + ] +] + + + +MTP3MSG subclass: MTP3NetworkManagementMSG [ + + + + + MTP3NetworkManagementMSG class >> h0Chm [ + + ^2r0001 + ] + + MTP3NetworkManagementMSG class >> h0Dlm [ + + ^2r1000 + ] + + MTP3NetworkManagementMSG class >> h0Ecm [ + + ^2r0010 + ] + + MTP3NetworkManagementMSG class >> h0Fcm [ + + ^2r0011 + ] + + MTP3NetworkManagementMSG class >> h0Mim [ + + ^2r0110 + ] + + MTP3NetworkManagementMSG class >> h0Rsm [ + + ^2r0101 + ] + + MTP3NetworkManagementMSG class >> h0Tfm [ + + ^2r0100 + ] + + MTP3NetworkManagementMSG class >> h0Trm [ + + ^2r0111 + ] + + MTP3NetworkManagementMSG class >> h0Ufc [ + + ^2r1010 + ] + + MTP3NetworkManagementMSG class >> h1CBA [ + + ^2r0110 + ] + + MTP3NetworkManagementMSG class >> h1CBD [ + + ^2r0101 + ] + + MTP3NetworkManagementMSG class >> h1COA [ + + ^2r0010 + ] + + MTP3NetworkManagementMSG class >> h1COO [ + + ^2r0001 + ] + + MTP3NetworkManagementMSG class >> h1CNP [ + + ^2r0100 + ] + + MTP3NetworkManagementMSG class >> h1CNS [ + + ^2r0011 + ] + + MTP3NetworkManagementMSG class >> h1CSS [ + + ^2r0010 + ] + + MTP3NetworkManagementMSG class >> h1DLC [ + + ^2r0001 + ] + + MTP3NetworkManagementMSG class >> h1ECA [ + + ^2r0010 + ] + + MTP3NetworkManagementMSG class >> h1ECO [ + + ^2r0001 + ] + + MTP3NetworkManagementMSG class >> h1RCT [ + + ^2r0001 + ] + + MTP3NetworkManagementMSG class >> h1TFC [ + + ^2r0010 + ] + + MTP3NetworkManagementMSG class >> h1LFU [ + + ^2r0110 + ] + + MTP3NetworkManagementMSG class >> h1LIA [ + + ^2r0011 + ] + + MTP3NetworkManagementMSG class >> h1LID [ + + ^2r0101 + ] + + MTP3NetworkManagementMSG class >> h1LIN [ + + ^2r0001 + ] + + MTP3NetworkManagementMSG class >> h1LLT [ + + ^2r0111 + ] + + MTP3NetworkManagementMSG class >> h1LRT [ + + ^2r1000 + ] + + MTP3NetworkManagementMSG class >> h1LUA [ + + ^2r0100 + ] + + MTP3NetworkManagementMSG class >> h1LUN [ + + ^2r0010 + ] + + MTP3NetworkManagementMSG class >> h1RSR [ + + ^2r0010 + ] + + MTP3NetworkManagementMSG class >> h1RST [ + + ^2r0001 + ] + + MTP3NetworkManagementMSG class >> h1TFA [ + + ^2r0101 + ] + + MTP3NetworkManagementMSG class >> h1TFP [ + + ^2r0001 + ] + + MTP3NetworkManagementMSG class >> h1TFR [ + + ^2r0011 + ] + + MTP3NetworkManagementMSG class >> h1TRA [ + + ^2r0001 + ] + + MTP3NetworkManagementMSG class >> h1UPU [ + + ^2r0001 + ] + + MTP3NetworkManagementMSG class >> isServiceCompatible: aServiceIndicator [ + + ^aServiceIndicator serviceIndicator + = MTP3ServiceIndicators signallingNetworkManagement + ] +] + + + +MTP3NetworkManagementMSG subclass: MTP3TRMMSG [ + + + + + MTP3TRMMSG class >> h0 [ + ^self h0Trm + ] + + MTP3TRMMSG class >> humanName [ + ^'Traffic-restart-allowed message' + ] +] + + + +MTP3NetworkManagementMSG subclass: MTP3CHMMSG [ + + + + + MTP3CHMMSG class >> h0 [ + ^self h0Chm + ] + + MTP3CHMMSG class >> humanName [ + ^'Changeover and changeback messages' + ] +] + + + +MTP3NetworkManagementMSG subclass: MTP3ECMMSG [ + + + + + MTP3ECMMSG class >> h0 [ + ^self h0Ecm + ] + + MTP3ECMMSG class >> humanName [ + ^'Emergency-changeover message' + ] +] + + + +MTP3LinkTestMSG subclass: MTP3SLTMMSG [ + + + + + MTP3SLTMMSG class >> h1 [ + ^self h1SLTM + ] + + MTP3SLTMMSG class >> humanName [ + ^'signalling link test acknowledgement message' + ] +] + + + +MTP3CHMMSG subclass: MTP3CBAMSG [ + + + + + MTP3CBAMSG class >> h1 [ + ^self h1CBA + ] + + MTP3CBAMSG class >> humanName [ + ^'Changeback-acknowledgement signal' + ] +] + + + +MTP3CHMMSG subclass: MTP3COOMSG [ + + + + + MTP3COOMSG class >> h1 [ + ^self h1COO + ] + + MTP3COOMSG class >> humanName [ + ^'Changeover-order signal' + ] +] + + + +MTP3Field subclass: MTP3Label [ + | dpc opc slc | + + + + + MTP3Label class >> parseFrom: aStream [ + | slc opc dpc tmp | + tmp := aStream next: 4. + + "TODO: Use the GSMBitfield or a bitreader" + slc := (tmp at: 4) bitAnd: 16r0F. + dpc := tmp first. + dpc := dpc bitOr: ((tmp second bitAnd: 2r00111111) bitShift: 8). + opc := tmp second bitShift: -6. + opc := opc bitOr: (tmp third bitShift: 2). + opc := opc bitOr: ((tmp fourth bitAnd: 2r00001111) bitShift: 10). + ^(MTP3Label new) + dpc: dpc; + opc: opc; + slc: slc; + yourself + ] + + dpc [ + + ^dpc + ] + + opc [ + + ^opc + ] + + slc [ + + ^slc + ] + + dpc: aDpc [ + + dpc := aDpc + ] + + opc: anOpc [ + + opc := anOpc + ] + + slc: aSlc [ + + slc := aSlc + ] + + writeOn: aBuffer [ + + | data w_slc w_dpc w_opc | + w_slc := slc bitAnd: 2r111. + w_dpc := dpc bitAnd: 2r11111111111111. + w_opc := opc bitAnd: 2r11111111111111. + data := (w_dpc bitOr: (w_opc bitShift: 14)) + bitOr: (w_slc bitShift: 14 + 14). + aBuffer + putByte: ((data bitShift: 0) bitAnd: 16rFF); + putByte: ((data bitShift: -8) bitAnd: 16rFF); + putByte: ((data bitShift: -16) bitAnd: 16rFF); + putByte: ((data bitShift: -24) bitAnd: 16rFF) + ] +] + + + +MTP3NetworkManagementMSG subclass: MTP3RSMMSG [ + + + + + MTP3RSMMSG class >> h0 [ + ^self h0Rsm + ] + + MTP3RSMMSG class >> humanName [ + ^'Signalling-route-set-test message' + ] +] + + + +MTP3RSMMSG subclass: MTP3RSTMSG [ + + + + + MTP3RSTMSG class >> h1 [ + ^self h1RST + ] + + MTP3RSTMSG class >> humanName [ + ^'Signalling-route-set-test signal for prohibited destination' + ] +] + + + +MTP3CHMMSG subclass: MTP3CBDMSG [ + + + + + MTP3CBDMSG class >> h1 [ + ^self h1CBD + ] + + MTP3CBDMSG class >> humanName [ + ^'Changeback-declaration signal' + ] +] + + + +MTP3LinkTestMSG subclass: MTP3SLTAMSG [ + + + + + MTP3SLTAMSG class >> h1 [ + ^self h1SLTA + ] + + MTP3SLTAMSG class >> humanName [ + ^'Signalling link test message' + ] +] + + + +MTP3ECMMSG subclass: MTP3ECOMSG [ + + + + + MTP3ECOMSG class >> h1 [ + ^self h1ECO + ] + + MTP3ECOMSG class >> humanName [ + ^'Emergency-changeover-order signal' + ] +] + + + +MTP3NetworkManagementMSG subclass: MTP3DLMMSG [ + + + + + MTP3DLMMSG class >> h0 [ + ^self h0Dlm + ] + + MTP3DLMMSG class >> humanName [ + ^'Signalling-data-link-connection-order message' + ] +] + + + +MTP3DLMMSG subclass: MTP3CNPMSG [ + + + + + MTP3CNPMSG class >> h1 [ + ^self h1CNP + ] + + MTP3CNPMSG class >> humanName [ + ^'Connection-not-possible signal' + ] +] + + + +MTP3DLMMSG subclass: MTP3DLCMSG [ + + + + + MTP3DLCMSG class >> h1 [ + ^self h1DLC + ] + + MTP3DLCMSG class >> humanName [ + ^'Signalling-data-link-connection-order signal' + ] +] + + + +MTP3DLMMSG subclass: MTP3CNSMSG [ + + + + + MTP3CNSMSG class >> h1 [ + ^self h1CNS + ] + + MTP3CNSMSG class >> humanName [ + ^'Connection-not-successful signal' + ] +] + + + +MTP3DLMMSG subclass: MTP3CSSMSG [ + + + + + MTP3CSSMSG class >> h1 [ + ^self h1CSS + ] + + MTP3CSSMSG class >> humanName [ + ^'Connection-successful signal' + ] +] + + + +MTP3RSMMSG subclass: MTP3RSRMSG [ + + + + + MTP3RSRMSG class >> h1 [ + ^self h1RSR + ] + + MTP3RSRMSG class >> humanName [ + ^'Signalling-route-set-test signal for restricted destination (national option)' + ] +] + + + +MTP3CHMMSG subclass: MTP3COAMSG [ + + + + + MTP3COAMSG class >> h1 [ + ^self h1COA + ] + + MTP3COAMSG class >> humanName [ + ^'Changeover-acknowledgement signal' + ] +] + + + +MTP3NetworkManagementMSG subclass: MTP3MIMMSG [ + + + + + MTP3MIMMSG class >> h0 [ + ^self h0Mim + ] + + MTP3MIMMSG class >> humanName [ + ^'Management inhibit messages' + ] +] + + + +MTP3MIMMSG subclass: MTP3LIAMSG [ + + + + + MTP3LIAMSG class >> h1 [ + ^self h1LIA + ] + + MTP3LIAMSG class >> humanName [ + ^'Link inhibit acknowledgement signal' + ] +] + + + +MTP3MIMMSG subclass: MTP3LINMSG [ + + + + + MTP3LINMSG class >> h1 [ + ^self h1LIN + ] + + MTP3LINMSG class >> humanName [ + ^'Link inhibit signal' + ] +] + + + +MTP3MIMMSG subclass: MTP3LFUMSG [ + + + + + MTP3LFUMSG class >> h1 [ + ^self h1LFU + ] + + MTP3LFUMSG class >> humanName [ + ^'Link forced uninhibit signal' + ] +] + + + +MTP3MIMMSG subclass: MTP3LIDMSG [ + + + + + MTP3LIDMSG class >> h1 [ + ^self h1LID + ] + + MTP3LIDMSG class >> humanName [ + ^'Link inhibit denied signal' + ] +] + + + +MTP3MIMMSG subclass: MTP3LUAMSG [ + + + + + MTP3LUAMSG class >> h1 [ + ^self h1LUA + ] + + MTP3LUAMSG class >> humanName [ + ^'Link uninhibit acknowledgement signal' + ] +] + + + +MTP3MIMMSG subclass: MTP3LUNMSG [ + + + + + MTP3LUNMSG class >> h1 [ + ^self h1LUN + ] + + MTP3LUNMSG class >> humanName [ + ^'Link uninhibit signal' + ] +] + + + +MTP3MIMMSG subclass: MTP3LLTMSG [ + + + + + MTP3LLTMSG class >> h1 [ + ^self h1LLT + ] + + MTP3LLTMSG class >> humanName [ + ^'Link local inhibit test signal' + ] +] + + + +MTP3NetworkManagementMSG subclass: MTP3FCMMSG [ + + + + + MTP3FCMMSG class >> h0 [ + ^self h0Fcm + ] + + MTP3FCMMSG class >> humanName [ + ^'Signalling-traffic-flow-control messages' + ] +] + + + +MTP3FCMMSG subclass: MTP3TFCMSG [ + + + + + MTP3TFCMSG class >> humanName [ + ^'Transfer-controlled signal' + ] +] + + + +MTP3FCMMSG subclass: MTP3RCTMSG [ + + + + + MTP3RCTMSG class >> humanName [ + ^'Signalling-route-set-congestion-test signal' + ] +] + + + +MTP3TRMMSG subclass: MTP3TRAMSG [ + + + + + MTP3TRAMSG class >> h1 [ + ^self h1TRA + ] + + MTP3TRAMSG class >> humanName [ + ^'Traffic-restart-allowed signal' + ] +] + + + +MTP3Field subclass: MTP3ServiceIndicators [ + | serviceIndicator subServiceField | + + + + + MTP3ServiceIndicators class >> broadbandIsdnUserPart [ + + ^2r1001 + ] + + MTP3ServiceIndicators class >> dataUserPartCallAndCircuit [ + + ^2r0110 + ] + + MTP3ServiceIndicators class >> dataUserPartFacilityAndCancellation [ + + ^2r0111 + ] + + MTP3ServiceIndicators class >> isdnUserPart [ + + ^2r0101 + ] + + MTP3ServiceIndicators class >> reservedMtpTestingUserPart [ + + ^2r1000 + ] + + MTP3ServiceIndicators class >> satelliteIsdnUserPart [ + + ^2r1010 + ] + + MTP3ServiceIndicators class >> sccp [ + + ^2r0011 + ] + + MTP3ServiceIndicators class >> serviceSpare [ + + ^2r0010 + ] + + MTP3ServiceIndicators class >> signallingNetworkManagement [ + + ^2r0000 + ] + + MTP3ServiceIndicators class >> signallingNetworkTestingAndMaintenance [ + + ^2r0001 + ] + + MTP3ServiceIndicators class >> telephoneUserPart [ + + ^2r0100 + ] + + MTP3ServiceIndicators class >> internationalNetwork [ + + ^2r0000 + ] + + MTP3ServiceIndicators class >> nationalNetwork [ + + ^2r1000 + ] + + MTP3ServiceIndicators class >> reservedNationalUse [ + + ^2r1100 + ] + + MTP3ServiceIndicators class >> subServiceSpare [ + + ^2r0100 + ] + + MTP3ServiceIndicators class >> parseFrom: aStream [ + + | byte | + byte := aStream next. + ^(self new) + serviceIndicator: (byte bitAnd: 2r1111); + subServiceField: (byte bitShift: -4); + yourself + ] + + serviceIndicator: anIndicator [ + + serviceIndicator := anIndicator + ] + + subServiceField: aSubServiceField [ + + subServiceField := aSubServiceField + ] + + serviceIndicator [ + + ^serviceIndicator + ] + + subServiceField [ + + ^subServiceField + ] + + writeOn: aMsg [ + + | data | + data := (subServiceField bitShift: 4) bitAnd: 2r11110000. + data := (serviceIndicator bitAnd: 2r1111) bitOr: data. + aMsg putByte: data + ] +] + + + +MTP3NetworkManagementMSG subclass: MTP3TFMMSG [ + + + + + MTP3TFMMSG class >> h0 [ + ^self h0Tfm + ] + + MTP3TFMMSG class >> humanName [ + ^'Transfer-prohibited-transfer-allowed-transfer-restricted messages' + ] +] + + + +MTP3TFMMSG subclass: MTP3TFAMSG [ + + + + + MTP3TFAMSG class >> h1 [ + ^self h1TFA + ] + + MTP3TFAMSG class >> humanName [ + ^'Transfer-allowed signal' + ] +] + + + +MTP3TFMMSG subclass: MTP3TFRMSG [ + + + + + MTP3TFRMSG class >> h1 [ + ^self h1TFR + ] + + MTP3TFRMSG class >> humanName [ + ^'Transfer-restricted signal (national option)' + ] +] + + + +MTP3TFMMSG subclass: MTP3TFPMSG [ + + + + + MTP3TFPMSG class >> h1 [ + ^self h1TFP + ] + + MTP3TFPMSG class >> humanName [ + ^'Transfer-prohibited signal' + ] +] + + + +MTP3NetworkManagementMSG subclass: MTP3UFCMSG [ + + + + + MTP3UFCMSG class >> h0 [ + ^self h0Ufc + ] + + MTP3UFCMSG class >> humanName [ + ^'User part flow control messages' + ] +] + + + +MTP3UFCMSG subclass: MTP3UPUMSG [ + + + + + MTP3UPUMSG class >> h1 [ + ^self h1UPU + ] + + MTP3UPUMSG class >> humanName [ + ^'User part unavailable signal' + ] +] + + + +MTP3ECMMSG subclass: MTP3ECAMSG [ + + + + + MTP3ECAMSG class >> h1 [ + ^self h1ECA + ] + + MTP3ECAMSG class >> humanName [ + ^'Emergency-changeover-acknowledgement signal' + ] +] + + + +MTP3MIMMSG subclass: MTP3LRTMSG [ + + + + + MTP3LRTMSG class >> h1 [ + ^self h1LRT + ] + + MTP3LRTMSG class >> humanName [ + ^'Link remote inhibit test signal' + ] +] + diff --git a/osmo-st-network/mtp3/MTP3MessagesTests.st b/osmo-st-network/mtp3/MTP3MessagesTests.st new file mode 100644 index 0000000..ec9e86f --- /dev/null +++ b/osmo-st-network/mtp3/MTP3MessagesTests.st @@ -0,0 +1,101 @@ +TestCase subclass: MTP3LabelTest [ + + + + + testParseFrom [ + | data stream label | + data := #(16r01 16r80 16r00 16r00) asByteArray. + stream := data readStream. + label := MTP3Label parseFrom: stream. + self assert: stream atEnd. + self assert: label dpc = 1. + self assert: label opc = 2. + self assert: label slc = 0. + self assert: label toMessage asByteArray = data + ] +] + + + +TestCase subclass: MTP3SLTAMSGTest [ + + + + + testParsing [ + | data stream msg | + data := #(16r81 16r02 16r40 16r00 16r00 16r21 16rE0 16r47 16r53 16r4D 16r4D 16r4D 16r53 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r00) + asByteArray. + stream := data readStream. + msg := MTP3MSG parseFrom: stream. + self assert: stream atEnd. + self assert: msg class = MTP3SLTAMSG. + self assert: msg testPattern + = #(16r47 16r53 16r4D 16r4D 16r4D 16r53 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r00) + asByteArray. + self assert: msg toMessage asByteArray = data + ] +] + + + +TestCase subclass: MTP3SLTMMSGTest [ + + + + + testParsing [ + | data stream msg | + data := #(16r81 16r02 16r40 16r00 16r00 16r11 16rE0 16r47 16r53 16r4D 16r4D 16r4D 16r53 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r00) + asByteArray. + stream := data readStream. + msg := MTP3MSG parseFrom: stream. + self assert: stream atEnd. + self assert: msg class = MTP3SLTMMSG. + self assert: msg testPattern + = #(16r47 16r53 16r4D 16r4D 16r4D 16r53 16r00 16r00 16r00 16r00 16r00 16r00 16r00 16r00) + asByteArray. + self assert: msg toMessage asByteArray = data + ] +] + + + +TestCase subclass: MTP3ServiceIndicatorsTest [ + + + + + testParseFrom [ + | data stream field | + data := #(16r81) asByteArray. + stream := data readStream. + field := MTP3ServiceIndicators parseFrom: stream. + self assert: stream atEnd. + self assert: field subServiceField = MTP3ServiceIndicators nationalNetwork. + self assert: field serviceIndicator + = MTP3ServiceIndicators signallingNetworkTestingAndMaintenance. + self assert: field toMessage asByteArray = data + ] +] + + + +TestCase subclass: MTP3HeadingTest [ + + + + + testParsing [ + | data stream field | + data := #(16r14) asByteArray. + stream := data readStream. + field := MTP3Heading parseFrom: stream. + self assert: stream atEnd. + self assert: field h0 = MTP3TFMMSG h0. + self assert: field h1 = MTP3TFPMSG h1. + self assert: field toMessage asByteArray = data + ] +] + diff --git a/osmo-st-network/osmo/LogAreaOsmo.st b/osmo-st-network/osmo/LogAreaOsmo.st new file mode 100644 index 0000000..cf76b1d --- /dev/null +++ b/osmo-st-network/osmo/LogAreaOsmo.st @@ -0,0 +1,38 @@ +" + (C) 2013 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 . +" + +LogArea subclass: LogAreaOsmo [ + + + + + LogAreaOsmo class >> areaDescription [ + ^'Osmo socket/connection releated code' + ] + + LogAreaOsmo class >> areaName [ + ^#osmo + ] + + LogAreaOsmo class >> default [ + ^(self new) + enabled: true; + minLevel: LogLevel debug; + yourself + ] +] diff --git a/osmo-st-network/osmo/OsmoAppConnection.st b/osmo-st-network/osmo/OsmoAppConnection.st new file mode 100644 index 0000000..29d33d2 --- /dev/null +++ b/osmo-st-network/osmo/OsmoAppConnection.st @@ -0,0 +1,95 @@ +" + (C) 2011-2013 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 . +" + +OsmoStreamSocketBase subclass: OsmoAppConnection [ + | writeQueue demuxer muxer dispatcher token connect_block | + + + + OsmoAppConnection class >> new [ + ^(self basicNew) + hostname: '127.0.0.1'; + port: 4250; + yourself + ] + + initializeDispatcher [ + | ipa | + "Allow another class to register handlers" + dispatcher := IPADispatcher new. + dispatcher initialize. + connect_block ifNotNil: [connect_block value: dispatcher]. + ipa := (IPAProtoHandler new) + registerOn: dispatcher; + muxer: muxer; + token: token; + yourself + ] + + nextPut: aData [ + muxer nextPut: aData with: IPAConstants protocolOsmoCTRL + ] + + nextPut: aData with: aConstant [ + muxer nextPut: aData with: aConstant + ] + + token: aToken [ + token := aToken. + ] + + onConnect: aBlock [ + + "Call the block when the socket is being connected and the dispatcher + is set-up. The callback will have the dispatcher as parameter." + connect_block := aBlock. + ] + + createConnection: aHostname port: aPort [ + + ^ Sockets.Socket remote: aHostname port: aPort. + ] + + connect [ + + super connect. + writeQueue := SharedQueue new. + demuxer := IPADemuxer initOn: socket. + muxer := IPAMuxer initOn: writeQueue. + self initializeDispatcher. + ] + + sendOne [ + | msg | + + + msg := writeQueue next. + socket nextPutAllFlush: msg. + ] + + dispatchOne [ + | msg | + + + msg := demuxer next. + dispatcher dispatch: msg first with: msg second. + ] +] + diff --git a/osmo-st-network/osmo/OsmoCtrlConnection.st b/osmo-st-network/osmo/OsmoCtrlConnection.st new file mode 100644 index 0000000..29fbaf9 --- /dev/null +++ b/osmo-st-network/osmo/OsmoCtrlConnection.st @@ -0,0 +1,43 @@ +" + (C) 2011-2013 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 . +" + +OsmoAppConnection subclass: OsmoCtrlConnection [ + | ctrlBlock | + + + onCtrlData: aBlock [ + + ctrlBlock := aBlock + ] + + handleCTRL: aCtrl [ + + ctrlBlock value: aCtrl. + ] + + initializeDispatcher [ + super initializeDispatcher. + dispatcher + addHandler: IPAConstants protocolOsmoCTRL + on: self with: #handleCTRL:. + ] + + sendCtrlData: aData [ + self nextPut: aData with: IPAConstants protocolOsmoCTRL + ] +] diff --git a/osmo-st-network/osmo/OsmoCtrlGrammar.st b/osmo-st-network/osmo/OsmoCtrlGrammar.st new file mode 100644 index 0000000..b96f211 --- /dev/null +++ b/osmo-st-network/osmo/OsmoCtrlGrammar.st @@ -0,0 +1,283 @@ +" + (C) 2011-2013 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 . +" + +PP.PPCompositeParser subclass: CtrlGrammar [ + + + + start [ + + ^ self message + ] + + message [ + + ^ self trapMessage / self notSupported + ] + + notSupported [ + + ^ #any asParser plus. + ] + + trapMessage [ + + ^ 'TRAP' asParser trim, + self identifier trim, + self variable trim, + #any asParser plus flatten + ] + + identifier [ + + ^ #digit asParser plus flatten + ] + + variable [ + + ^ self variablePart plus + ] + + variablePart [ + + ^ (#digit asParser plus / #letter asParser / $- asParser / $_ asParser) plus flatten, + $. asParser optional + ] +] + +Object subclass: CtrlCmd [ + | msg | + + + + CtrlCmd class >> with: aMsg [ + + ^ self new + instVarNamed: #msg put: aMsg; + yourself + ] + + isTrap [ + + ^ false + ] + + msg [ + + ^ msg + ] +] + +CtrlCmd subclass: CtrlTrap [ + + + + CtrlTrap class >> isFor: aPath [ + + ^ self subclassResponsibility + ] + + CtrlTrap class >> isFor: aPath value: aValue [ + ^self isFor: aPath + ] + + CtrlTrap class >> findTrapFor: nodes [ + + CtrlTrap allSubclassesDo: [:trap | + (trap isFor: nodes third value: nodes fourth) + ifTrue: [^trap with: nodes]]. + ^ CtrlTrap new + ] +] + +CtrlTrap subclass: CtrlLocationTrap [ + | net_nr bsc_nr bts_nr location | + + + + CtrlLocationTrap class >> isFor: aPath [ + + ^ aPath last first = 'location-state'. + ] + + CtrlLocationTrap class >> with: aList [ + ^ self new + net: (aList third at: 2) first; + bsc: (aList third at: 4) first; + bts: (aList third at: 6) first; + location: aList fourth; + yourself + ] + + net: aStr [ + + net_nr := aStr asNumber + ] + + bsc: aStr [ + + bsc_nr := aStr asNumber + ] + + bts: aBts [ + + bts_nr := aBts asNumber + ] + + location: aLoc [ + + location := aLoc substrings: ','. + location size = 8 ifFalse: [ + ^ self error: 'Failed to parse location'. + ]. + ] + + net [ + + ^ net_nr + ] + + bsc [ + + ^ bsc_nr + ] + + bts [ + ^ bts_nr + ] + + locTimeStamp [ + + ^ location at: 1 + ] + + locState [ + + ^ location at: 2 + ] + + locLat [ + + ^ location at: 3 + ] + + locLon [ + + ^ location at: 4 + ] + + locHeight [ + + ^ location at: 5 + ] + + trxAvailable [ + + ^ (location at: 6) = 'operational' + ] + + trxAdminLock [ + + ^ (location at: 7) = 'locked' + ] + + rfPolicy [ + + ^ location at: 8 + ] + + rfPolicyOn [ + + ^ self rfPolicy = 'on' + ] + + rfPolicyOff [ + + ^ self rfPolicy = 'off' + ] + + rfPolicyGrace [ + + ^ self rfPolicy = 'grace' + ] + + rfPolicyUnknown [ + + ^ self rfPolicy = 'unknown' + ] +] + +CtrlTrap subclass: CtrlCallStatTrap [ + | dict | + + + + CtrlCallStatTrap class >> isFor: aPath [ + + + (aPath at: 1) first = 'net' ifFalse: [^false]. + (aPath at: 3) first = 'bsc' ifFalse: [^false]. + (aPath at: 5) first = 'call_stats' ifFalse: [^false]. + (aPath at: 6) first = 'v2' ifFalse: [^false]. + ^ true + ] + + CtrlCallStatTrap class >> with: aMsg [ + + + ^ (super with: aMsg) + extractMessage; + yourself. + ] + + extractMessage [ + | var data | + + "Create aliases to avoid the first first second last madness" + var := msg at: 3. + dict := Dictionary new. + dict at: 'nat_id' put: (var at: 2) first. + dict at: 'bsc_id' put: (var at: 4) first. + + data := msg at: 4. + data := data substrings: ','. + data do: [:each | + | split | + split := each substrings: '='. + dict at: split first put: split second. + ]. + ] + + at: aName [ + ^ dict at: aName + ] +] + +CtrlGrammar subclass: CtrlParser [ + + + + trapMessage [ + ^ super trapMessage => [:nodes | + CtrlTrap findTrapFor: nodes]. + ] + + notSupported [ + ^ super notSupported => [:nodes | CtrlCmd with: (String withAll: nodes)] + ] +] diff --git a/osmo-st-network/osmo/OsmoCtrlGrammarTest.st b/osmo-st-network/osmo/OsmoCtrlGrammarTest.st new file mode 100644 index 0000000..37e6b7f --- /dev/null +++ b/osmo-st-network/osmo/OsmoCtrlGrammarTest.st @@ -0,0 +1,104 @@ +"All rights reserved" + +PP.PPCompositeParserTest subclass: CtrlGrammarTest [ + + + + CtrlGrammarTest class >> packageNamesUnderTest [ + + ^ #('CtrlGrammar') + ] + + parserClass [ + + ^ CtrlGrammar + ] + + testLocationStateTrap [ + | data res | + + + data := 'TRAP 0 net.0.bsc.7.bts.0.location-state 1,fix2d,4.860000,53.941111,0.000000,inoperational,unlocked,on'. + + res := self parse: data. + ] +] + +PP.PPCompositeParserTest subclass: CtrlParserTest [ + + + + CtrlParserTest class >> packageNamesUnderTest [ + + ^ #('CtrlParser') + ] + + parserClass [ + + ^ CtrlParser + ] + + testLocationStateTrap [ + | data res | + + + data := 'TRAP 0 net.1.bsc.7.bts.6.location-state 1,fix2d,1.000000,2.000000,3.000000,inoperational,unlocked,on'. + + res := self parse: data. + self assert: res net = 1. + self assert: res bsc = 7. + self assert: res bts = 6. + self assert: res locTimeStamp = 1 asString. + self assert: res locLat = '1.000000'. + self assert: res locLon = '2.000000'. + self assert: res locHeight = '3.000000'. + + self assert: res rfPolicyOn. + self deny: res trxAvailable. + self deny: res trxAdminLock. + ] + + testResponseeError [ + | data res | + + data := 'ERROR 386 Command not found'. + res := self parse: data. + self assert: res msg = data. + ] + + testCallStatIsFor [ + | data | + data := #(('net' $. ) ('1' $. ) ('bsc' $. ) ('7' $. ) ('call_stats' $. ) ('v2' nil ) ). + self assert: (CtrlCallStatTrap isFor: data). + ] + + testCallStat [ + | data res | + + + data := 'TRAP 0 net.1.bsc.7.call_stats.v2 mg_ip_addr=213.167.134.139,mg_port=60480,endpoint_ip_addr=127.0.0.1,endpoint_port=33342,nat_pkt_in=208,nat_pkt_out=0,nat_bytes_in=6055,nat_bytes_out=0,nat_jitter=145,nat_pkt_loss=-1,bsc_pkt_in=0,bsc_pkt_out=208,bsc_bytes_in=0,bsc_bytes_out=6055,bsc_jitter=0,bsc_pkt_loss=0,sccp_src_ref=100,sccp_dst_ref=1000'. + + res := self parse: data. + self + assert: (res at: 'nat_id') = '1'; + assert: (res at: 'bsc_id') = '7'; + assert: (res at: 'mg_ip_addr') = '213.167.134.139'; + assert: (res at: 'mg_port') = '60480'; + assert: (res at: 'endpoint_ip_addr') = '127.0.0.1'; + assert: (res at: 'endpoint_port') = '33342'; + assert: (res at: 'nat_pkt_in') = '208'; + assert: (res at: 'nat_pkt_out') = '0'; + assert: (res at: 'nat_bytes_in') = '6055'; + assert: (res at: 'nat_bytes_out') = '0'; + assert: (res at: 'nat_jitter') = '145'; + assert: (res at: 'nat_pkt_loss') = '-1'; + assert: (res at: 'bsc_pkt_in') = '0'; + assert: (res at: 'bsc_pkt_out') = '208'; + assert: (res at: 'bsc_bytes_in') = '0'; + assert: (res at: 'bsc_bytes_out') = '6055'; + assert: (res at: 'bsc_jitter') = '0'; + assert: (res at: 'bsc_pkt_loss') = '0'; + assert: (res at: 'sccp_src_ref') = '100'; + assert: (res at: 'sccp_dst_ref') = '1000'. + ] +] diff --git a/osmo-st-network/osmo/OsmoCtrlLogging.st b/osmo-st-network/osmo/OsmoCtrlLogging.st new file mode 100644 index 0000000..907efd9 --- /dev/null +++ b/osmo-st-network/osmo/OsmoCtrlLogging.st @@ -0,0 +1,13 @@ +"I represent the logging areas" + +Osmo.LogArea subclass: LogAreaCTRL [ + + LogAreaCTRL class >> areaName [ ^ #ctrl ] + LogAreaCTRL class >> areaDescription [ ^ 'Osmo CTRL handling' ] + LogAreaCTRL class >> default [ + ^ self new + enabled: true; + minLevel: Osmo.LogLevel debug; + yourself + ] +] diff --git a/osmo-st-network/osmo/OsmoStreamSocketBase.st b/osmo-st-network/osmo/OsmoStreamSocketBase.st new file mode 100644 index 0000000..a8fd539 --- /dev/null +++ b/osmo-st-network/osmo/OsmoStreamSocketBase.st @@ -0,0 +1,165 @@ +" + (C) 2011-2013 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: OsmoStreamSocketBase [ + | socket hostname port tx_proc rx_proc started | + + + + + OsmoStreamSocketBase class >> connectionException [ + + ^ SystemExceptions.FileError + ] + + hostname: aHostname [ + + hostname := aHostname + ] + + port: aPort [ + + port := aPort + ] + + hostname [ + + ^hostname + ] + + port [ + + ^port + ] + + targetDescription [ + + ^(WriteStream on: String new) + nextPutAll: hostname; + nextPut: $:; + nextPutAll: port asString; + contents + ] + + connect [ + + socket ifNotNil: [socket close]. + socket := self createConnection: hostname port: port + ] + + start [ + + started := true. + + [ + self logNotice: ('Attempting to connect to ', + self targetDescription) area: #osmo. + self connect + ] on: self class connectionException do: [ + self logError: ('Failed to connect to ', + self targetDescription) area: #osmo. + ^Osmo.TimerScheduler instance scheduleInSeconds: 1 block: [self reconnect]]. + + rx_proc := + [Processor activeProcess name: 'OsmoAppConnection-RX ', self targetDescription. + [self driveDispatch] repeat] fork. + tx_proc := [Processor activeProcess name: 'OsmoAppConnection-TX ', self targetDescription. + [self driveSend] repeat] fork + ] + + stop [ + + started := false. + self terminate + "A reconnect timer might be running right now" + ] + + terminate [ + + tx_proc ifNotNil: [tx_proc terminate]. + rx_proc ifNotNil: [rx_proc terminate]. + socket ifNotNil: + [[socket close.] ensure: [ socket := nil ]]. + ] + + driveDispatch [ + + + [ + self dispatchOne + ] on: SystemExceptions.EndOfStream do: [:e | + self logError: ('OsmoApplication dispatch eof on ', + self targetDescription) area: #osmo. + self scheduleReconnect + ] on: SystemExceptions.FileError do: [:e | + self logError: ('OsmoApplication dispatch file-error on ', + self targetDescription) area: #osmo. + self scheduleReconnect + ] on: Error do: [:e | + e logException: ('OsmoApplication dispatch error on ', + self targetDescription) area: #osmo. + self scheduleReconnect + ] + ] + + driveSend [ + + [ + self sendOne + ] on: SystemExceptions.EndOfStream do: [:e | + self logError: ('OsmoApplication send eof on ', + self targetDescription) area: #osmo. + self scheduleReconnect + ] on: Error do: [:e | + e logException: ('OsmoApplication send error on ', + self targetDescription) area: #osmo. + self scheduleReconnect + ] + ] + + reconnect [ + + self logNotice: ('Going to reconnect socket to ', self targetDescription) area: #osmo. + self terminate. + started ifTrue: [self start] + ] + + scheduleReconnect [ + + socket ifNotNil: [socket close. socket := nil]. + TimerScheduler instance scheduleInSeconds: 1 block: [self reconnect]. + "We are done now" + Processor activeProcess terminate + ] + + createConnection: aHostname port: aPort [ + + self subclassResponsibility + ] + + dispatchOne [ + + self subclassResponsibility + ] + + sendOne [ + + self subclassResponsibility + ] +] diff --git a/osmo-st-network/osmo/OsmoUDPSocket.st b/osmo-st-network/osmo/OsmoUDPSocket.st new file mode 100644 index 0000000..7dafddc --- /dev/null +++ b/osmo-st-network/osmo/OsmoUDPSocket.st @@ -0,0 +1,116 @@ +" + (C) 2010-2012 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: OsmoUDPSocket [ + | socket queue rx tx net_exit name on_data | + + + + OsmoUDPSocket class >> new [ + + ^ super new + initialize; + yourself + ] + + initialize [ + + queue := SharedQueue new. + net_exit := Semaphore new. + ] + + name: aName [ + + name := aName + ] + + onData: aBlock [ + + on_data := aBlock + ] + + start: aSocket [ + + socket := aSocket. + + "Receive datagrams from the socket..." + rx := self startRXProcess. + + "Send data to the MGWs" + tx := [ + [Processor activeProcess name: name, ' TX'. + self runTXProcess] ensure: [net_exit signal]] fork. + ] + + startRXProcess [ + ^ [[Processor activeProcess name: name, ' RX'. + self runRXProcess] ensure: [net_exit signal]] fork. + ] + + runRXProcess [ + + + [ | data | + socket ensureReadable. + socket isOpen ifFalse: [ + ^self logNotice: name, ' socket closed.' area: #core]. + + data := socket next. + on_data value: data. + ] repeat. + ] + + runTXProcess [ + + + [ | data | + data := queue next. + data = nil ifTrue: [ + ^self logNotice: name, ' TX asked to quit.' area: #core]. + + socket nextPut: data. + ] repeat. + ] + + stop [ + + + socket ifNil: [^self]. + + "Close" + socket close. + queue nextPut: nil. + + "Wait for the process to exit" + self logNotice: name, ' waiting for IO handlers to exit.' area: #core. + net_exit + wait; + wait. + + "Forget things" + socket := nil. + tx := nil. + rx := nil. + ] + + queueData: aData [ + + queue nextPut: aData + ] +] diff --git a/osmo-st-network/package.xml b/osmo-st-network/package.xml new file mode 100644 index 0000000..eb6eb1f --- /dev/null +++ b/osmo-st-network/package.xml @@ -0,0 +1,87 @@ + + OsmoNetwork + Osmo + + OsmoLogging + OsmoCore + PetitParser + Sockets + Parser + + core/Extensions.st + core/ExtensionsGST.st + core/MessageStructure.st + core/MessageBuffer.st + core/LogAreas.st + core/TLV.st + isup/ISUP.st + isup/isup_generated.st + isup/ISUPExtensions.st + ipa/IPAConstants.st + ipa/IPAConstantsGST.st + ipa/IPADispatcher.st + ipa/IPAMuxer.st + ipa/IPAProtoHandler.st + ipa/IPAMsg.st + sccp/SCCP.st + sccp/SCCPAddress.st + sccp/SCCPGlobalTitle.st + sccp/SCCPGlobalTitleTranslation.st + mtp3/MTP3Messages.st + ua/XUA.st + + m2ua/M2UAConstants.st + m2ua/M2UAStates.st + m2ua/M2UATag.st + m2ua/M2UAMSG.st + m2ua/M2UAMessages.st + m2ua/M2UAStates.st + m2ua/M2UAAspStateMachine.st + m2ua/M2UAApplicationServerProcess.st + m2ua/M2UALayerManagement.st + m2ua/M2UATerminology.st + m2ua/M2UAExamples.st + + + + osmo/LogAreaOsmo.st + osmo/OsmoUDPSocket.st + osmo/OsmoCtrlLogging.st + osmo/OsmoCtrlGrammar.st + osmo/OsmoStreamSocketBase.st + osmo/OsmoAppConnection.st + osmo/OsmoCtrlConnection.st + + + + PetitParserTests + Osmo.SCCPTests + Osmo.IPATests + Osmo.IPAGSTTests + Osmo.IPAMsgTests + Osmo.MessageBufferTest + Osmo.ISUPGeneratedTest + Osmo.OsmoUDPSocketTest + Osmo.TLVDescriptionTest + Osmo.CtrlGrammarTest + Osmo.CtrlParserTest + + Osmo.M2UAMSGTests + Osmo.M2UAApplicationServerProcessTest + Osmo.M2UAAspStateMachineTest + + Osmo.MTP3LabelTest + Osmo.MTP3SLTAMSGTest + Osmo.MTP3SLTMMSGTest + Osmo.MTP3ServiceIndicatorsTest + Osmo.MTP3HeadingTest + + Tests.st + core/TLVTests.st + isup/ISUPTests.st + ipa/IPATests.st + osmo/OsmoCtrlGrammarTest.st + m2ua/M2UATests.st + mtp3/MTP3MessagesTests.st + + diff --git a/osmo-st-network/pharo-porting/changes_for_pharo.st b/osmo-st-network/pharo-porting/changes_for_pharo.st new file mode 100644 index 0000000..d9678a8 --- /dev/null +++ b/osmo-st-network/pharo-porting/changes_for_pharo.st @@ -0,0 +1,59 @@ +""" +The following changes need to be kept for pharo. +""" +OsmoUDPSocketTest extend [ + createSocket [ + ^ Socket newUDP + ] +] + +OsmoUDPSocket extend [ + startRXProcess [ + ^ [[[ + Processor activeProcess name: name, ' RX'. + self runRXProcess + ] on: ConnectionClosed do: [] + ] ensure: [net_exit signal]] fork. + ] +] + +OsmoAppConnection extend [ + createConnection: aHostname port: aPort [ + + ^(SocketStream openConnectionToHostNamed: aHostname port: aPort) + binary; + noTimeout; + yourself + ] +] + +OsmoStreamSocketBase extend [ + driveDispatch [ + + [ + [self dispatchOne] on: ConnectionClosed do: [:e | + self logError: 'OsmoApplication dispatch failed.' area: #osmo. + self scheduleReconnect] + ] on: Error do: [:e | + e logException: 'OsmoApplication error' area: #osmo. + self scheduleReconnect] + ] + + driveSend [ + + + [ + self sendOne. + ] on: ConnectionClosed do: [:e | + e logException: 'OsmoAppConnection send failed' area: #osmo. + self scheduleReconnect. + ] + ] +] + +OsmoStreamSocketBase class extend [ + connectionException [ + + ^ConnectionTimedOut + ] +] diff --git a/osmo-st-network/pharo-porting/compat_for_pharo.st b/osmo-st-network/pharo-porting/compat_for_pharo.st new file mode 100644 index 0000000..2d4f237 --- /dev/null +++ b/osmo-st-network/pharo-porting/compat_for_pharo.st @@ -0,0 +1,60 @@ +ByteArray extend [ + shortAt: index [ + + + "This is not signed right now" + ^ self ushortAt: index + ] + + ushortAt: index [ + + + ^ ((self at: index + 1) bitShift: 8) bitOr: (self at: index) + ] + + uintAt: index [ + + + | byte1 byte2 byte3 byte4 | + byte1 := (self at: index). + byte2 := (self at: index + 1) bitShift: 8. + byte3 := (self at: index + 2) bitShift: 16. + byte4 := (self at: index + 3) bitShift: 24. + + ^ (((byte4 bitOr: byte3) bitOr: byte2) bitOr: byte1) + ] +] + +NotFound class extend [ + signalOn: anObject what: aMessage [ + + ^ self new + object: anObject; + messageText: aMessage; + signal + ] +] + +Socket extend [ + ensureReadable [ + + ^ self isValid + ] + + isOpen [ + + ^ self isConnected + ] + + next [ + | data | + + data := ByteArray new: 2048. + + ">>#waitForData will block forever.. we use some form of polling" + [self dataAvailable] whileFalse: [ + [self waitForDataFor: 10] on: ConnectionTimedOut do: []]. + self receiveUDPDataInto: data. + ^data + ] +] diff --git a/osmo-st-network/sccp/SCCP.st b/osmo-st-network/sccp/SCCP.st new file mode 100644 index 0000000..9f16a98 --- /dev/null +++ b/osmo-st-network/sccp/SCCP.st @@ -0,0 +1,784 @@ +" + (C) 2010-2012 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: SCCPHelper [ + + + + SCCPHelper class >> msgCr [ ^ 16r01 ] + SCCPHelper class >> msgCc [ ^ 16r02 ] + SCCPHelper class >> msgCref [ ^ 16r03 ] + SCCPHelper class >> msgRlsd [ ^ 16r04 ] + SCCPHelper class >> msgRlc [ ^ 16r05 ] + SCCPHelper class >> msgDt1 [ ^ 16r06 ] + SCCPHelper class >> msgDt2 [ ^ 16r07 ] + SCCPHelper class >> msgAk [ ^ 16r08 ] + SCCPHelper class >> msgUdt [ ^ 16r09 ] + SCCPHelper class >> msgUdts [ ^ 16r0A ] + SCCPHelper class >> msgEd [ ^ 16r0B ] + SCCPHelper class >> msgEa [ ^ 16r0C ] + SCCPHelper class >> msgRsr [ ^ 16r0D ] + SCCPHelper class >> msgRsc [ ^ 16r0E ] + SCCPHelper class >> msgErr [ ^ 16r0F ] + SCCPHelper class >> msgIt [ ^ 16r10 ] + SCCPHelper class >> msgXudt [ ^ 16r11 ] + SCCPHelper class >> msgXudts[ ^ 16r12 ] + SCCPHelper class >> msgLudt [ ^ 16r13 ] + SCCPHelper class >> msgLudts[ ^ 16r14 ] + + SCCPHelper class >> pncData [ ^ 16r0F ] + SCCPHelper class >> pncEoO [ ^ 16r00 ] + + SCCPHelper class >> createCR: src dest: dest data: aData [ + + ^ (SCCPConnectionRequest initWith: src dest: dest data: aData) + toMessage. + ] + + SCCPHelper class >> createRLSD: src dest: dest cause: cause [ + + ^ (SCCPConnectionReleased initWithDst: dest src: src cause: cause) + toMessage. + ] + + SCCPHelper class >> createDT1: dst data: data [ + + ^ (SCCPConnectionData initWith: dst data: data) + toMessage. + ] +] + +Object subclass: SCCPPNC [ + | dict | + + + + + SCCPPNC class >> parseFrom: aPnc [ + | dict pnc | + + + pnc := aPnc. + dict := Dictionary new. + + [pnc isEmpty not] whileTrue: [ + | type | + type := pnc at: 1. + + type = SCCPHelper pncEoO + ifTrue: [ + pnc := ByteArray new. + ] + ifFalse: [ + | size data | + size := pnc at: 2. + data := pnc copyFrom: 3 to: 3 + size - 1. + pnc := pnc copyFrom: 3 + size. + dict at: type put: data. + ]. + ]. + + ^ (self new) + dict: dict; + yourself. + ] + + at: aKey put: aValue [ + + self dict at: aKey put: aValue. + ] + + at: aKey [ + + ^ self dict at: aKey. + ] + + dict [ + + ^ dict ifNil: [dict := Dictionary new.] + ] + + dict: aDict [ + + dict := aDict. + ] + + writeOn: aMsg [ + + self dict keysAndValuesDo: [:key :val | + | dat | + dat := val toMessageOrByteArray. + + aMsg putByte: key. + aMsg putByte: dat size. + aMsg putByteArray: dat. + ]. + + aMsg putByte: SCCPHelper pncEoO. + ] +] + +Object subclass: SCCPAddrReference [ + + + + + SCCPAddrReference class >> store: anAddress on: aMsg [ + "Store the threee bytes of an sccp address on a messagebuffer" + + + aMsg putByte: ((anAddress bitAnd: 16r000000FF) bitShift: -0). + aMsg putByte: ((anAddress bitAnd: 16r0000FF00) bitShift: -8). + aMsg putByte: ((anAddress bitAnd: 16r00FF0000) bitShift: -16). + ] + + SCCPAddrReference class >> fromCData: anArray [ + | oct1 oct2 oct3 | + "Parse from an CArray" + + + oct1 := (anArray at: 0) bitShift: 0. + oct2 := (anArray at: 1) bitShift: 8. + oct3 := (anArray at: 2) bitShift: 16. + + ^ (oct1 bitOr: oct2) bitOr: oct3 + ] + + SCCPAddrReference class >> fromByteArray: anArray [ + | oct1 oct2 oct3 | + "Parse from a ByteArray" + + + oct1 := (anArray at: 1) bitShift: 0. + oct2 := (anArray at: 2) bitShift: 8. + oct3 := (anArray at: 3) bitShift: 16. + + ^ (oct1 bitOr: oct2) bitOr: oct3 + ] +] + +Object subclass: SCCPMessage [ + + + + SCCPMessage class >> decode: aByteArray [ + | type | + + type := aByteArray at: 1. + + SCCPMessage allSubclassesDo: [:each | + each msgType = type + ifTrue: [ + ^ each parseFrom: aByteArray. + ] + ]. + + "raise exception" + ^ Error signal: ('No handler for: <1p>' expandMacrosWith: type). + ] +] + +SCCPMessage subclass: SCCPConnectionRequest [ + | src dst pnc | + + + + + SCCPConnectionRequest class >> msgType [ + + ^ SCCPHelper msgCr + ] + + SCCPConnectionRequest class >> initWith: src dest: dest pnc: pnc [ + + ^ self new + src: src dest: dest pnc: pnc; + yourself + ] + + SCCPConnectionRequest class >> initWith: src dest: dest data: data [ + + | pnc | + pnc := SCCPPNC new. + pnc at: SCCPHelper pncData put: data. + + ^ self new + src: src dest: dest pnc: pnc; + yourself + ] + + SCCPConnectionRequest class >> parseFrom: aMsg [ + | src addr proto variable optional pnc | + + + src := SCCPAddrReference fromByteArray: (aMsg copyFrom: 2 to: 4). + proto := (aMsg at: 5) asInteger. + variable := (aMsg at: 6) asInteger. + optional := (aMsg at: 7) asInteger. + + "some sanity check" + proto ~= 2 ifTrue: [ + Exception signal: 'Proto should be two was ', proto asString. + ]. + + "parse the address" + addr := SCCPAddress parseFrom: (aMsg copyFrom: (6 + variable)). + + "parse the optional data" + pnc := SCCPPNC parseFrom: (aMsg copyFrom: (7 + optional)). + + ^ SCCPConnectionRequest initWith: src dest: addr pnc: pnc. + ] + + src [ + + ^ src + ] + + dest [ + + ^ dst + ] + + data [ + + ^ pnc at: SCCPHelper pncData. + ] + + data: aData [ + + pnc at: SCCPHelper pncData put: aData. + ] + + src: aSrc dest: aDest pnc: aPnc [ + + src := aSrc. + dst := aDest. + pnc := aPnc. + ] + + writeOn: aMsg [ + + | dat len addr | + + addr := dst asByteArray. + + aMsg putByte: self class msgType. + SCCPAddrReference store: src on: aMsg. + "store proto_class, variable_called, optional_start" + aMsg putByte: 2. + aMsg putByte: 2. + aMsg putByte: 1 + addr size. + + aMsg putByteArray: addr. + + " place the data now " + pnc writeOn: aMsg. + ^ aMsg. + ] +] + +SCCPMessage subclass: SCCPConnectionConfirm [ + | src dst pnc | + + + + + SCCPConnectionConfirm class >> msgType [ + + ^ SCCPHelper msgCc + ] + + SCCPConnectionConfirm class >> initWithSrc: aSrc dst: aDst [ + + ^ self new + src: aSrc dst: aDst; + yourself + ] + + SCCPConnectionConfirm class >> parseFrom: aMsg [ + | src dst proto optional | + + + dst := SCCPAddrReference fromByteArray: (aMsg copyFrom: 2 to: 4). + src := SCCPAddrReference fromByteArray: (aMsg copyFrom: 5 to: 7). + proto := aMsg at: 8. + optional := aMsg at: 9. + + "TODO: Add additional items" + ^ self new + src: src dst: dst; + yourself + ] + + writeOn: aMsg [ + + + aMsg putByte: SCCPHelper msgCc. + SCCPAddrReference store: dst on: aMsg. + SCCPAddrReference store: src on: aMsg. + aMsg putByte: 2. + aMsg putByte: 1. + self pnc writeOn: aMsg. + ] + + src: aSrc dst: aDst [ + + src := aSrc. + dst := aDst. + ] + + src [ + + ^ src + ] + + dst [ + + ^ dst + ] + + pnc [ + + ^ pnc ifNil: [ pnc := SCCPPNC new. ] + ] +] + +SCCPMessage subclass: SCCPConnectionData [ + | dst data | + + + + + SCCPConnectionData class >> msgType [ + + ^ SCCPHelper msgDt1 + ] + + SCCPConnectionData class >> initWith: dst data: data [ + + ^ (self new) + dst: dst; + data: data; + yourself. + ] + + SCCPConnectionData class >> parseFrom: aByteArray [ + | more_data var_start addr size data | + + + addr := SCCPAddrReference fromByteArray: (aByteArray copyFrom: 2). + more_data := aByteArray at: 5. + more_data = 0 ifFalse: [ + Error signal: 'Fragmented data is not supported.'. + ]. + + var_start := aByteArray at: 6. + size := aByteArray at: 6 + var_start. + data := aByteArray copyFrom: (6 + var_start + 1) to: (6 + var_start + size). + + ^ SCCPConnectionData initWith: addr data: data. + ] + + dst: aDst [ + + dst := aDst. + ] + + data: aData [ + + data := aData. + + data size > 16rFF ifTrue: [ + self error: ('Data must be < 256 in size but was <1p>' expandMacrosWith: data size) + ]. + ] + + dst [ + + ^ dst + ] + + data [ + + ^ data + ] + + writeOn: aMsg [ + | dat | + + + aMsg putByte: self class msgType. + SCCPAddrReference store: dst on: aMsg. + aMsg putByte: 0. + aMsg putByte: 1. + + dat := data toMessageOrByteArray. + aMsg putByte: dat size. + aMsg putByteArray: dat. + + ^ aMsg + ] +] + +SCCPMessage subclass: SCCPConnectionReleased [ + | src dst cause pnc | + + + + + SCCPConnectionReleased class >> msgType [ + + ^ SCCPHelper msgRlsd + ] + + SCCPConnectionReleased class >> initWithDst: aDst src: aSrc cause: aCause [ + + + ^ self new + dst: aDst; + src: aSrc; + cause: aCause; + yourself. + ] + + SCCPConnectionReleased class >> parseFrom: aByteArray [ + | dst src cause | + + + dst := SCCPAddrReference fromByteArray: (aByteArray copyFrom: 2). + src := SCCPAddrReference fromByteArray: (aByteArray copyFrom: 5). + cause := aByteArray at: 8. + + ^ SCCPConnectionReleased initWithDst: dst src: src cause: cause. + ] + + dst [ + + ^ dst + ] + + src [ + + ^ src + ] + + cause [ + + ^ cause + ] + + dst: aDst [ + + dst := aDst + ] + + src: aSrc [ + + src := aSrc + ] + + cause: aCause [ + + cause := aCause + ] + + pnc [ + + ^ pnc ifNil: [pnc := SCCPPNC new] + ] + + + writeOn: aMsg [ + + aMsg putByte: self class msgType. + SCCPAddrReference store: dst on: aMsg. + SCCPAddrReference store: src on: aMsg. + aMsg putByte: cause. + aMsg putByte: 1. + self pnc writeOn: aMsg. + ] +] + +SCCPMessage subclass: SCCPConnectionReleaseComplete [ + | dst src | + + + + + SCCPConnectionReleaseComplete class >> msgType [ + + ^ SCCPHelper msgRlc. + ] + + SCCPConnectionReleaseComplete class >> initWithDst: aDst src: aSrc [ + + ^ self new + dst: aDst; src: aSrc; + yourself + ] + + SCCPConnectionReleaseComplete class >> parseFrom: aByteArray [ + + ^ self new + dst: (SCCPAddrReference fromByteArray: (aByteArray copyFrom: 2 to: 4)); + src: (SCCPAddrReference fromByteArray: (aByteArray copyFrom: 5 to: 7)); + yourself + ] + + dst [ + + ^ dst + ] + + dst: aDst [ + + dst := aDst. + ] + + src [ + + ^ src + ] + + src: aSrc [ + + src := aSrc. + ] + + writeOn: aMsg [ + + aMsg putByte: self class msgType. + SCCPAddrReference store: dst on: aMsg. + SCCPAddrReference store: src on: aMsg. + ] +] + +SCCPMessage subclass: SCCPUDT [ + | called calling data error udtClass | + + + + + SCCPUDT class >> msgType [ + + ^ SCCPHelper msgUdt + ] + + SCCPUDT class >> initWith: aCalled calling: aCalling data: aData [ + + ^ self new + calledAddr: aCalled; + callingAddr: aCalling; + data: aData; + yourself + ] + + SCCPUDT class >> parseFrom: aByteArray [ + | called calledData calling callingData data dataData dataSize | + + + called := aByteArray at: 3. + calledData := aByteArray copyFrom: (3 + called). + + calling := aByteArray at: 4. + callingData := aByteArray copyFrom: (4 + calling). + + data := aByteArray at: 5. + dataSize := aByteArray at: (5 + data). + dataData := aByteArray copyFrom: (6 + data) to: 5 + data + dataSize. + + ^ (SCCPUDT initWith: (SCCPAddress parseFrom: calledData) + calling: (SCCPAddress parseFrom: callingData) + data: dataData) + udtClass: ((aByteArray at: 2) bitAnd: 16r0F); + errorHandling: ((aByteArray at: 2) bitShift: -4); + yourself. + ] + + calledAddr: aCalled [ + + called := aCalled + ] + + calledAddr [ + + ^ called + ] + + callingAddr: aCalling [ + + calling := aCalling + ] + + callingAddr [ + + ^ calling + ] + + data [ + + ^ data + ] + + data: aData [ + + data := aData. + ] + + errorHandling: aStrategy [ + + error := aStrategy. + ] + + errorHandling [ + + ^ error ifNil: [0] + ] + + udtClass: aClass [ + + udtClass := aClass. + ] + + udtClass [ + + ^ udtClass ifNil: [0] + ] + + writeOn: aMsg [ + | calledData callingData dat | + + calledData := called asByteArray. + callingData := calling asByteArray. + + aMsg putByte: self class msgType. + aMsg putByte: (((self errorHandling bitAnd: 16r0F) bitShift: 4) bitOr: self udtClass). + + "pointers" + aMsg putByte: 3. + aMsg putByte: 1 + calledData size + 1. + aMsg putByte: calledData size + callingData size + 1. + + "the data" + aMsg putByteArray: calledData. + aMsg putByteArray: callingData. + + dat := data toMessageOrByteArray. + aMsg putByte: dat size. + aMsg putByteArray: dat. + ] +] + +SCCPMessage subclass: SCCPInactivityTest [ + | src dst proto seq credit | + + + + + SCCPInactivityTest class >> msgType [ + + ^ SCCPHelper msgIt + ] + + SCCPInactivityTest class >> initWithDst: aDst src: aSrc [ + + ^ self new + dst: aDst; + src: aSrc; + yourself. + ] + + SCCPInactivityTest class >> parseFrom: aByteArray [ + | dst src proto seq credit | + + + dst := SCCPAddrReference fromByteArray: (aByteArray copyFrom: 2). + src := SCCPAddrReference fromByteArray: (aByteArray copyFrom: 5). + ^ (self initWithDst: dst src: src) + instVarNamed: #proto put: (aByteArray at: 8); + instVarNamed: #seq put: (aByteArray copyFrom: 9 to: 10); + instVarNamed: #credit put: (aByteArray at: 11); + yourself + ] + + src: aSrc [ + + src := aSrc. + ] + + src [ + + ^ src + ] + + dst: aDst [ + + dst := aDst + ] + + dst [ + + ^ dst + ] + + credit [ + + ^ credit ifNil: [0] + ] + + credit: aCredit [ + + credit := aCredit + ] + + protoClass [ + + ^ proto ifNil: [0] + ] + + protoClass: aClass [ + + proto := aClass. + ] + + seq [ + + ^ seq ifNil: [ByteArray new: 2] + ] + + seq: aSeq [ + + seq := aSeq. + ] + + writeOn: aMsg [ + + aMsg putByte: self class msgType. + SCCPAddrReference store: dst on: aMsg. + SCCPAddrReference store: src on: aMsg. + aMsg putByte: self protoClass. + aMsg putByteArray: self seq. + aMsg putByte: self credit. + ] +] diff --git a/osmo-st-network/sccp/SCCPAddress.st b/osmo-st-network/sccp/SCCPAddress.st new file mode 100644 index 0000000..5d240c6 --- /dev/null +++ b/osmo-st-network/sccp/SCCPAddress.st @@ -0,0 +1,253 @@ +" + (C) 2010-2012 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: SCCPAddress [ + | subSystemNumber globalTitle routedOnSsn pointCode gti_ind | + + + + + SCCPAddress class >> ssnNotKnown [ ^ 0 ] + SCCPAddress class >> ssnSCCPMgnt [ ^ 1 ] + SCCPAddress class >> ssnITURsrvd [ ^ 2 ] + SCCPAddress class >> ssnISUP [ ^ 3 ] + SCCPAddress class >> ssnOMA [ ^ 4 ] + SCCPAddress class >> ssnMAP [ ^ 5 ] + SCCPAddress class >> ssnHLR [ ^ 6 ] + SCCPAddress class >> ssnVLR [ ^ 7 ] + SCCPAddress class >> ssnMSC [ ^ 8 ] + SCCPAddress class >> ssnEIC [ ^ 9 ] + SCCPAddress class >> ssnAUC [ ^ 10 ] + SCCPAddress class >> ssnISUPSRV [ ^ 11 ] + SCCPAddress class >> ssnReserved [ ^ 12 ] + SCCPAddress class >> ssnBroadISDN[ ^ 13 ] + SCCPAddress class >> ssnTCTest [ ^ 14 ] + SCCPAddress class >> ssnSGSN [ ^149 ] + + SCCPAddress class >> createWith: ssn [ + + ^self createWith: ssn pointCode: nil + ] + + SCCPAddress class >> createWith: ssn poi: aPointCode [ + + self deprecated: 'Use >>#createWith:pointCode: instead'. + ^self createWith: ssn pointCode: aPointCode + ] + + SCCPAddress class >> createWith: ssn pointCode: aPointCode [ + + ^(self new) + ssn: ssn; + routedOnSSN: true; + pointCode: aPointCode; + yourself + ] + + SCCPAddress class >> createForSSN: aSymbol [ + + ^ self createWith: (self perform: ('ssn', aSymbol asUppercase) asSymbol) + ] + + SCCPAddress class >> parseFrom: aByteArray [ + | routed_ssn gti_ind gti len ai ssn pointCode dat | + + pointCode := nil. + len := aByteArray at: 1. + ai := aByteArray at: 2. + + "Copy the address" + dat := aByteArray copyFrom: 3 to: len + 1. + + "Point Code" + (ai bitAnd: 1) = 1 + ifTrue: [ + pointCode := (dat ushortAt: 1). + dat := dat copyFrom: 3. + ]. + + "SSN" + routed_ssn := (ai bitAnd: 16r40) = 16r40. + ssn := dat at: 1. + dat := dat copyFrom: 2. + + "GTI" + gti_ind := (ai bitAnd: 16r3C) bitShift: -2. + gti := dat copyFrom: 1. + + ^ self new + ssn: ssn; + pointCode: pointCode; + routedOnSSN: routed_ssn; + gti: gti indicator: gti_ind; + yourself. + ] + + routedOnSSN: aFlag [ + + self routedOnSubSystenNumber: aFlag + ] + + routedOnSubSystenNumber: aFlag [ + + routedOnSsn := aFlag + ] + + routedOnSSN [ + + ^ routedOnSsn ifNil: [false] + ] + + gti [ + + ^ self globalTitle + ] + + globalTitle [ + + ^ globalTitle + ] + + gtiInd [ + + ^ gti_ind + ] + + globalTitle: aGlobalTitle indicator: aGtiInd [ + + globalTitle := aGlobalTitle. + gti_ind := aGtiInd bitAnd: 16rF. + ] + + gti: aGlobalTitle indicator: aGtiInd [ + + self globalTitle: aGlobalTitle indicator: aGtiInd + ] + + gtiAsParsed [ + + ^self parseGlobalTitle + ] + + parseGlobalTitle [ + + ^ gti_ind = 0 + ifTrue: [nil] + ifFalse: [SCCPGlobalTitle initWith: gti_ind data: globalTitle]. + ] + + gtiFromAddr: aGlobalTitle [ + + gti_ind := aGlobalTitle class subType. + globalTitle := aGlobalTitle asByteArray. + ] + + poi: aPointCode [ + + self deprecated: 'Use >>#pointCode: instead'. + self pointCode: aPointCode + ] + + poi [ + + self deprecated: 'Use >>#pointCode instead'. + ^self pointCode + ] + + pointCode [ + + ^pointCode + ] + + pointCode: aPointCode [ + "When a non-nil point code is set the pointcode indicator will be set in the + address information." + + + pointCode := aPointCode + ] + + ssn: aSubSystemNumber [ + + "deprecated" + self subSystemNumber: aSubSystemNumber + ] + + subSystemNumber: aSubSystemNumber [ + subSystemNumber := aSubSystemNumber + ] + + ssn [ + + ^ self subSystemNumber + ] + + subSystemNumber [ + + ^ subSystemNumber + ] + + asByteArray [ + "Most simple address storing routine" + | ai data | + + + data := OrderedCollection new. + + "Create the Address Information" + ai := 0. + + "SSN indicator" + ai := ai bitOr: 2. + self routedOnSSN ifTrue: [ + ai := ai bitOr: 64. + ]. + + "Point Code" + pointCode ifNotNil: [ + ai := ai bitOr: 1. + ]. + + "GTI Indicator" + gti_ind ifNotNil: [ + ai := ai bitOr: (gti_ind bitShift: 2). + ]. + + data add: ai. + + "POC" + pointCode ifNotNil: [ + data add: ((pointCode bitAnd: 16r00FF) bitShift: 0). + data add: ((pointCode bitAnd: 16rFF00) bitShift: -8) + ]. + + "SSN" + data add: subSystemNumber. + + "GTI" + gti_ind ifNotNil: [ + globalTitle do: [:each | data add: each ]. + ]. + + data addFirst: data size. + + ^ data asByteArray + ] +] + diff --git a/osmo-st-network/sccp/SCCPGlobalTitle.st b/osmo-st-network/sccp/SCCPGlobalTitle.st new file mode 100644 index 0000000..71942aa --- /dev/null +++ b/osmo-st-network/sccp/SCCPGlobalTitle.st @@ -0,0 +1,122 @@ +" + (C) 2010-2013 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: SCCPGlobalTitle [ + | indicator nai data | + + + + + SCCPGlobalTitle class >> gtiIndNoGTI [ ^ 0 ] + SCCPGlobalTitle class >> gtiIndGTI [ ^ 1 ] + SCCPGlobalTitle class >> gtiIndTransOnlyGTI [ ^ 2 ] + SCCPGlobalTitle class >> gtiIndTransNumbrPlanAndEnc [ ^ 3 ] + SCCPGlobalTitle class >> gtiIndTransNumbrAndMore [ ^ 4 ] + + SCCPGlobalTitle class >> naiUnknown [ ^ 0 ] + SCCPGlobalTitle class >> naiSubscriber [ ^ 1 ] + SCCPGlobalTitle class >> naiReservedNational [ ^ 2 ] + SCCPGlobalTitle class >> naiNationalSign [ ^ 3 ] + SCCPGlobalTitle class >> naiInternationalNumber [ ^ 4 ] + + SCCPGlobalTitle class >> npUnknown [ ^ 0 ] + SCCPGlobalTitle class >> npISDN [ ^ 1 ] + SCCPGlobalTitle class >> npGeneric [ ^ 2 ] + SCCPGlobalTitle class >> npData [ ^ 3 ] + SCCPGlobalTitle class >> npTelex [ ^ 4 ] + SCCPGlobalTitle class >> npMaritime [ ^ 5 ] + SCCPGlobalTitle class >> npLand [ ^ 6 ] + SCCPGlobalTitle class >> npMobile [ ^ 7 ] + + SCCPGlobalTitle class >> esUnknown [ ^ 0 ] + SCCPGlobalTitle class >> esBCDOdd [ ^ 1 ] + SCCPGlobalTitle class >> esBCDEven [ ^ 2 ] + SCCPGlobalTitle class >> esNational [ ^ 3 ] + + SCCPGlobalTitle class >> initWith: gti_ind data: gti [ + + + self allSubclassesDo: [:each | + each subType = gti_ind + ifTrue: [ + ^ each initWith: gti. + ]. + ]. + + ^ self error: ('Unhandled gti indicator: <1p>' expandMacrosWith: gti_ind). + ] + + SCCPGlobalTitle class >> map: aDigit [ + + ^ (aDigit >= 0 and: [aDigit <= 9]) + ifTrue: [ (aDigit + 48) asCharacter ] + ifFalse: [ $N ] + ] + + SCCPGlobalTitle class >> unmap: aChar [ + | digit | + + digit := aChar asInteger. + ^ (digit >= 48 and: [digit <= 57]) + ifTrue: [ digit - 48 ] + ifFalse: [ 16rF ]. + ] + + SCCPGlobalTitle class >> parseAddr: data encoding: aEnc [ + | odd split | + + (aEnc = 1 or: [aEnc = 2]) ifFalse: [ + ^ self error: 'Only BCD number encoding supported.' + ]. + + split := OrderedCollection new. + data do: [:each | + split add: (self map: (each bitAnd: 16r0F)). + split add: (self map: ((each bitAnd: 16rF0) bitShift: -4)). + ]. + + "Handle the odd case" + aEnc = 1 ifTrue: [ + split removeLast. + ]. + + ^ String withAll: split. + ] + + SCCPGlobalTitle class >> formatAddr: aNumber on: data [ + | nr odd | + + + nr := OrderedCollection new. + odd := aNumber size odd. + aNumber do: [:each | + nr add: (self unmap: each) + ]. + + odd ifTrue: [ + nr add: 16r0. + ]. + + 1 to: nr size by: 2 do: [:each| + | low high | + low := nr at: each. + high := nr at: each + 1. + data add: (low bitOr: (high bitShift: 4)). + ]. + ] +] diff --git a/osmo-st-network/sccp/SCCPGlobalTitleTranslation.st b/osmo-st-network/sccp/SCCPGlobalTitleTranslation.st new file mode 100644 index 0000000..6b1fde1 --- /dev/null +++ b/osmo-st-network/sccp/SCCPGlobalTitleTranslation.st @@ -0,0 +1,107 @@ +" + (C) 2010-2012 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 . +" + +SCCPGlobalTitle subclass: SCCPGlobalTitleTranslation [ + | trans plan nature addr | + + + + + SCCPGlobalTitleTranslation class >> subType [ ^ 4 ] + SCCPGlobalTitleTranslation class >> initWith: data [ + | enc | + + + enc := (data at: 2) bitAnd: 16r0F. + ^ self new + translation: (data at: 1); + plan: (((data at: 2) bitAnd: 16rF0) bitShift: -4); + nature: ((data at: 3) bitAnd: 16r7F); + addr: (self parseAddr: (data copyFrom: 4) encoding: enc); + yourself + ] + + translation [ + + ^ trans ifNil: [ 0 ] + ] + + translation: aTrans [ + + trans := aTrans + ] + + plan [ + + ^ plan + ] + + plan: aPlan [ + + plan := aPlan + ] + + encoding [ + + ^addr size odd + ifTrue: [1] + ifFalse: [2] + ] + + nature [ + + ^ nature + ] + + nature: aNai [ + + nature := aNai + ] + + address [ + + ^addr + ] + + addr [ + + ^self address + ] + + addr: anAddr [ + + addr := anAddr + ] + + asByteArray [ + | data | + + data := OrderedCollection new. + + "write the header" + data add: self translation. + data add: ((plan bitShift: 4) bitOr: self encoding). + data add: nature. + + "encode the number" + SCCPGlobalTitle formatAddr: addr on: data. + + ^ data asByteArray + ] +] diff --git a/osmo-st-network/ua/XUA.st b/osmo-st-network/ua/XUA.st new file mode 100644 index 0000000..e5fdb2c --- /dev/null +++ b/osmo-st-network/ua/XUA.st @@ -0,0 +1,116 @@ +" + (C) 2011-2012 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: UAConstants [ + " + " + + + + + UAConstants class >> clsMgmt [ ^ 0 ] + UAConstants class >> clsTrans [ ^ 1 ] + UAConstants class >> clsSSMN [ ^ 2 ] + UAConstants class >> clsASPSM [ ^ 3 ] + UAConstants class >> clsASPTM [ ^ 4 ] + UAConstants class >> clsQPTM [ ^ 5 ] + UAConstants class >> clsMAUP [ ^ 6 ] + UAConstants class >> clsSUA_LESS [ ^ 7 ] + UAConstants class >> clsSUA_CONN [ ^ 8 ] + UAConstants class >> clsRKM [ ^ 9 ] + UAConstants class >> clasIIM [ ^ 10 ] + + + UAConstants class >> maupReserved [ ^ 0 ] + UAConstants class >> maupData [ ^ 1 ] + UAConstants class >> maupEstReq [ ^ 2 ] + UAConstants class >> maupEstCon [ ^ 3 ] + UAConstants class >> maupRelReq [ ^ 4 ] + UAConstants class >> maupRelCon [ ^ 5 ] + UAConstants class >> maupRelInd [ ^ 6 ] + UAConstants class >> maupStateReq [ ^ 7 ] + UAConstants class >> maupStateCon [ ^ 8 ] + UAConstants class >> maupStateInd [ ^ 9 ] + UAConstants class >> maupDRetrReq [ ^ 10 ] + UAConstants class >> maupDRetrCon [ ^ 11 ] + UAConstants class >> maupDRetrInd [ ^ 12 ] + UAConstants class >> maupDRetrCompl [ ^ 13 ] + UAConstants class >> maupCongInd [ ^ 14 ] + UAConstants class >> maupDataAck [ ^ 15 ] + + UAConstants class >> aspsmReserved [ ^ 0 ] + UAConstants class >> aspsmUp [ ^ 1 ] + UAConstants class >> aspsmDown [ ^ 2 ] + UAConstants class >> aspsmBeat [ ^ 3 ] + UAConstants class >> aspsmUpAck [ ^ 4 ] + UAConstants class >> aspsmDownAck [ ^ 5 ] + UAConstants class >> aspsmBeatAck [ ^ 6 ] + + UAConstants class >> asptmReserved [ ^ 0 ] + UAConstants class >> asptmActiv [ ^ 1 ] + UAConstants class >> asptmInactiv [ ^ 2 ] + UAConstants class >> asptmActivAck [ ^ 3 ] + UAConstants class >> asptmInactivAck [ ^ 4 ] + + UAConstants class >> mgmtError [ ^ 0 ] + UAConstants class >> mgmtNtfy [ ^ 1 ] + + UAConstants class >> iimReserved [ ^ 0 ] + UAConstants class >> iimRegReq [ ^ 1 ] + UAConstants class >> iimRegRsp [ ^ 2 ] + UAConstants class >> iimDeregReq [ ^ 3 ] + UAConstants class >> iimDeregResp [ ^ 4 ] + + UAConstants class >> tagReserved [ ^ 0 ] + UAConstants class >> tagIdentInt [ ^ 1 ] + UAConstants class >> tagUnused1 [ ^ 2 ] + UAConstants class >> tagIdentText [ ^ 3 ] + UAConstants class >> tagInfo [ ^ 4 ] + UAConstants class >> tagUnused2 [ ^ 5 ] + UAConstants class >> tagUnused3 [ ^ 6 ] + UAConstants class >> tagDiagInf [ ^ 7 ] + UAConstants class >> tagIdentRange [ ^ 8 ] + UAConstants class >> tagBeatData [ ^ 9 ] + UAConstants class >> tagUnused4 [ ^ 10 ] + UAConstants class >> tagTraMode [ ^ 11 ] + UAConstants class >> tagErrCode [ ^ 12 ] + UAConstants class >> tagStatus [ ^ 13 ] + UAConstants class >> tagUnused5 [ ^ 14 ] + UAConstants class >> tagUnused6 [ ^ 15 ] + UAConstants class >> tagUnused7 [ ^ 16 ] + UAConstants class >> tagAspIdent [ ^ 17 ] + UAConstants class >> tagUnused8 [ ^ 18 ] + UAConstants class >> tagCorrelId [ ^ 19 ] + +] + +