smalltalk
/
osmo-st-all
Archived
1
0
Fork 0

Add 'osmo-st-network/' from commit 'cb55eb5dcf67fbe1ca02e12cd3ccc25df4847ee2'

git-subtree-dir: osmo-st-network
git-subtree-mainline: b9597ffde5
git-subtree-split: cb55eb5dcf
This commit is contained in:
Holger Hans Peter Freyther 2014-06-04 15:45:02 +02:00
commit 3ee982fe7a
101 changed files with 11691 additions and 0 deletions

1
osmo-st-network/.gitignore vendored Normal file
View File

@ -0,0 +1 @@
*.sw?

75
osmo-st-network/Makefile Normal file
View File

@ -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

1
osmo-st-network/README Normal file
View File

@ -0,0 +1 @@
osmo-network a module for networking (SCCP, M3UA, IPA) protocol handling

397
osmo-st-network/Tests.st Normal file
View File

@ -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 <http://www.gnu.org/licenses/>.
"
"Test Case for Osmo-Network"
TestCase subclass: SCCPTests [
<category: 'OsmoNetwork-Tests'>
SCCPTests class >> packageNamesUnderTest [
<category: 'accessing'>
^ #('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 [
<category: 'OsmoNetwork-Tests'>
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 [
<category: 'OsmoNetwork-M2UA-Tests'>
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 [
<category: 'OsmoNetwork-Tests'>
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.
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
"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 ].
]
]

View File

@ -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.
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Integer extend [
swap16 [
| tmp |
<category: '*OsmoNetwork-Message'>
tmp := self bitAnd: 16rFFFF.
^ (tmp bitShift: -8) bitOr: ((tmp bitAnd: 16rFF) bitShift: 8)
]
swap32 [
| tmp |
"Certainly not the most effective way"
<category: '*OsmoNetwork-Message'>
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 |
<category: '*OsmoNetwork-message'>
msg := Osmo.MessageBuffer new.
self writeOn: msg.
^ msg
]
toMessageOrByteArray [
<category: '*OsmoNetwork-Message'>
^ self toMessage
]
]
ByteArray extend [
toMessageOrByteArray [
<category: '*OsmoNetwork-Message'>
^ 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"
<category: '*OsmoNetwork-Message'>
^self nextBytes: 2 signed: false
]
nextBytes: n signed: signed [
"Private - Get an integer out of the next anInteger bytes in the stream"
<category: '*OsmoNetwork-Message'>
| 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"
<category: '*OsmoNetwork-Message'>
| 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"
<category: '*OsmoNetwork-Message'>
^self nextBytes: 2 signed: false
]
nextBytes: n signed: signed [
"Private - Get an integer out of the next anInteger bytes in the stream"
<category: '*OsmoNetwork-Message'>
| 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"
<category: '*OsmoNetwork-Message'>
| a |
a := self next.
^a isNil ifTrue: [a] ifFalse: [a asInteger]
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
BlockClosure extend [
value: arg1 value: arg2 value: arg3 value: arg4 [
<category: '*OsmoNetwork'>
"Evaluate the receiver passing arg1, arg2, arg3 and arg4 as the parameters"
<category: 'built ins'>
<primitive: VMpr_BlockClosure_value>
SystemExceptions.WrongArgumentCount signal
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Osmo.LogArea subclass: LogAreaSCCP [
<category: 'OsmoNetwork-SCCP'>
<comment: 'I am the debug area for SCCP.'>
LogAreaSCCP class >> areaName [ <category: 'accessing'> ^ #sccp ]
LogAreaSCCP class >> areaDescription [ <category: 'accessing'> ^ 'SCCP related' ]
LogAreaSCCP class >> default [
<category: 'creation'>
^ self new
enabled: true;
minLevel: Osmo.LogLevel debug;
yourself
]
]
Osmo.LogArea subclass: LogAreaIPA [
<category: 'OsmoNetwork-IPA'>
<comment: 'I am the debug area for IPA messages.'>
LogAreaIPA class >> areaName [ <category: 'accessing'> ^ #ipa ]
LogAreaIPA class >> areaDescription [ <category: 'accessing'> ^ 'IPA related' ]
LogAreaIPA class >> default [
<category: 'creation'>
^ self new
enabled: true;
minLevel: Osmo.LogLevel debug;
yourself
]
]
Osmo.LogArea subclass: LogAreaM2UA [
<category: 'OsmoNetwork-M2UA'>
<comment: 'I am the debug area for M2UA messages'>
LogAreaM2UA class >> areaName [ <category: 'accessing'> ^ #m2ua ]
LogAreaM2UA class >> areaDescription [ <category: 'accessing'> ^ 'MTP2 User Adaption' ]
LogAreaM2UA class >> default [
<category: 'creation'>
^ self new
enabled: true;
minLevel: Osmo.LogLevel debug;
yourself
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Collection subclass: MessageBuffer [
| chunks |
<category: 'OsmoNetwork-Message'>
<comment: 'A network buffer/creation class. Modeled after the msgb of osmocore'>
MessageBuffer class >> new [
<category: 'creation'>
^ (super new)
initialize;
yourself
]
initialize [
<category: 'accessing'>
chunks := OrderedCollection new.
]
toMessage [
<category: 'creation'>
^ self
]
prependByteArray: aByteArray [
<category: 'creation'>
chunks addFirst: aByteArray.
]
putByte: aByte [
<category: 'creation'>
chunks add: (ByteArray with: aByte)
]
putByteArray: aByteArray [
<category: 'creation'>
chunks add: aByteArray.
]
put16: aInt [
| data low high |
<category: 'creation'>
low := (aInt bitAnd: 16rFF).
high := (aInt bitShift: -8) bitAnd: 16rFF.
data := ByteArray with: low with: high.
chunks add: data.
]
putLen16: aInt [
| data low high |
<category: 'creation'>
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 |
<category: 'creation'>
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 [
<category: 'deprecated'>
^ self asByteArray.
]
size [
"Count of how much data we have collected"
<category: 'accessing'>
^ chunks inject: 0 into: [:acc :each | acc + each size ]
]
do: aBlock [
<category: 'accessing'>
chunks do: [:chunk |
chunk do: aBlock.
].
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
"
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 |
<category: 'OsmoNetwork-MSG'>
<comment: 'Attempt to have a DSL for messages'>
TLVDescriptionContainer class >> initWith: aType [
<category: 'creation'>
^ self new
instVarNamed: #type put: aType; yourself
]
TLVDescriptionContainer class >> findTLVDescription: aType [
<category: 'creation'>
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 |
<category: 'parsing'>
"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 |
<category: 'encoding'>
"This is a generic encoding method that will put the collection
onto a MessageBuffer class."
description := self findTLVDescription: aType.
^ description encodeCollection: aCollection.
]
type: aType [
<category: 'private'>
type := aType.
]
type [
<category: 'accessing'>
^ type
]
addFixed: aType [
<category: 'fields'>
self fields add: {#fixed. aType}
]
addOptional: aType [
<category: 'fields'>
self fields add: {#optional. aType}
]
addOptionals: aType [
<category: 'fields'>
"Optional Parameters that may appear more than once."
self fields add: {#optionals. aType}
]
addVariable: aType [
<category: 'fields'>
self fields add: {#variable. aType}
]
fields [
<category: 'fields'>
^ fields ifNil: [fields := OrderedCollection new]
]
fieldsDo: aBlock [
<category: 'fields'>
^ self fields do: [:each | aBlock value: each first value: each second]
]
filter: aFilter [
| lst |
<category: 'fields'>
lst := OrderedCollection new.
self fields inject: lst into: [:list :each |
each first = aFilter ifTrue: [
list add: each second.
].
list].
^ lst
]
filterdDo: aBlock filter: aFilter [
<category: 'private'>
^ self fields do: [:each |
each first = aFilter ifTrue: [
aBlock value: each first value: each second]].
]
fixed [
<category: 'private'>
^ self filter: #fixed
]
fixedDo: aBlock [
<category: 'private'>
^ self filterdDo: aBlock filter: #fixed.
]
variable [
<category: 'private'>
^ self filter: #variable
]
variableDo: aBlock [
<category: 'private'>
^ self filterdDo: aBlock filter: #variable.
]
optional [
<category: 'private'>
^ self filter: #optional
]
optionals [
<category: 'private'>
^ self filter: #optionals
]
parseFixed: aStream with: aClass into: decoded [
<category: 'decoding'>
decoded add: (aClass readFixedFrom: aStream).
^ true
]
parseField: aStream with: aClass into: decoded [
| len |
<category: 'private'>
"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 [
<category: 'decoding'>
^ self parseField: aStream with: aClass into: decoded.
]
parseOptional: aStream with: aClass into: decoded [
| tag len |
<category: 'decoding'>
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 [
<category: 'decoding'>
[
self parseOptional: aStream with: aClass into: decoded.
] whileTrue: [].
]
prepareOptional: aStream [
<category: 'decoding'>
"Nothing to be done here. Subclasses can manipulate the stream"
]
decodeByteStream: aStream [
| decoded first_optional |
<category: 'decoding'>
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 [
<category: 'encoding'>
(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 [
<category: 'encoding'>
(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 [
<category: 'encoding'>
(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 [
<category: 'encoding'>
"Subclasses can create their own state to allow jumping in the
stream or leave markers"
^ nil
]
writeFixedEnd: aStream state: aState [
<category: 'encoding'>
"Subclasses can use me to do something at the end of fixed messages."
]
writeVariableEnd: aStream state: aState [
<category: 'encoding'>
]
encodeCollection: aCollection [
| stream msg aState |
<category: 'encoding'>
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 |
<category: 'OsmoNetwork-MSG'>
<comment: 'The description of an Information Element'>
MSGField class >> isCompatible: aField [
<category: 'parsing'>
^ aField isKindOf: self.
]
MSGField class >> readVariableFrom: aStream length: aLength [
<category: 'parsing'>
"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 [
<category: 'accessing'>
^ self subclassResponsibility
]
MSGField class >> parameterValue [
<category: 'accessing'>
^ 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"
<category: 'accessing'>
^ 1
]
MSGField class >> octalLength [
<category: 'accessing'>
^ self subclassResponsibility
]
MSGField class >> isVarible [
<category: 'kind'>
"If this field is variable in length"
^ self subclassResponsibility
]
MSGField class >> isFixed [
<category: 'kind'>
"If this field is of a fixed length"
^ self subclassResponsibility
]
MSGField class >> maxLength [
<category: 'accessing'>
^ nil
]
data: aData [
<category: 'accessing'>
data := aData.
]
data [
<category: 'accessing'>
^ data
]
]
MSGField subclass: MSGFixedField [
<category: 'OsmoNetwork-MSG'>
<comment: 'I represent a fixed length field.'>
MSGFixedField class >> isVarible [ <category: 'kind'> ^ false ]
MSGFixedField class >> isFixed [ <category: 'kind'> ^ true ]
MSGFixedField class >> readFixedFrom: aStream [
<category: 'parsing'>
^ self new
data: (aStream next: self octalLength);
yourself
]
MSGFixedField class >> readVariableFrom: aStream length: aLength [
<category: 'parsing'>
aLength = self octalLength ifFalse: [
^ self error: 'The size needs to be exact'.
].
^ super readVariableFrom: aStream length: aLength
]
]
MSGField subclass: MSGVariableField [
<category: 'OsmoNetwork-MSG'>
<comment: 'I represent a variable sized field.'>
MSGVariableField class >> isVarible [ <category: 'kind'> ^ true ]
MSGVariableField class >> isFixed [ <category: 'kind'> ^ false ]
]

304
osmo-st-network/core/TLV.st Normal file
View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: TLVDescription [
| tag kind parse_class type inst_var min_size max_size len_size force_tag |
<category: 'OsmoNetwork-TLV'>
<comment: 'I am another attempt to express optional and mandatory fields.'>
TLVDescription class [
optional [
<category: 'presence'>
^ #optional
]
mandatory [
<category: 'presence'>
^ #mandatory
]
conditional [
<category: 'presence'>
^ #conditional
]
tagLengthValue [
<category: 'type'>
^ #tlv
]
tagValue [
<category: 'type'>
^ #tv
]
valueOnly [
<category: 'type'>
^ #valueOnly
]
tagOnly [
<category: 'type'>
^ #tagOnly
]
lengthValue [
<category: 'type'>
^#lv
]
new [
<category: 'creation'>
^ super basicNew
initialize;
yourself
]
]
initialize [
<category: 'creation'>
kind := self class mandatory.
type := self class tagLengthValue.
len_size := 1.
force_tag := false.
]
tag: aTag [
<category: 'creation'>
tag := aTag
]
tag [
<category: 'access'>
"The tag value for this tag inside the bytestream"
^ tag
]
minSize: aMin maxSize: aMax [
<category: 'size'>
"This only makes sense for *LV elements"
min_size := aMin.
max_size := aMax.
]
minSize: aMin [
min_size := aMin.
max_size := nil.
]
valueSize: aSize [
<category: 'size'>
^ self minSize: aSize maxSize: aSize.
]
valueSize [
^ max_size
]
isOptional [
<category: 'access'>
^ kind = self class optional
]
isMandatory [
<category: 'access'>
^ kind = self class mandatory
]
isConditional [
<category: 'access'>
^ kind = self class conditional
]
isFixedSize [
<category: 'access'>
^ type = self class tagValue or: [type = self class valueOnly].
]
hasLength [
<category: 'access'>
^ type = self class tagLengthValue or: [type = self class lengthValue]
]
isLen16 [
<category: 'access'>
^ self hasLength and: [len_size = 2]
]
isLen8 [
<category: 'access'>
^ self hasLength and: [len_size = 1]
]
isForcedTag [
<category: 'access'>
^ force_tag
]
hasTag [
<category: 'access'>
^type ~= self class lengthValue and: [type ~= self class valueOnly]
]
needsTag [
<category: 'access'>
^force_tag or: [self hasTag and: [self isOptional or: [self isConditional]]].
]
presenceKind: aKind [
<category: 'creation'>
"Is this required, optional, variable?"
kind := aKind
]
beOptional [
<category: 'creation'>
self presenceKind: self class optional.
]
beConditional [
<category: 'creation'>
self presenceKind: self class conditional.
]
beForceTagged [
<category: 'creation'>
"Write a tag even if this element is mandatory"
force_tag := true.
]
beTagOnly [
<category: 'creation'>
self typeKind: self class tagOnly.
]
beTV [
<category: 'creation'>
self typeKind: self class tagValue
]
beTLV [
<category: 'creation'>
self typeKind: self class tagLengthValue
]
beLV [
<category: 'creation'>
self typeKind: self class lengthValue
]
beLen16 [
<category: 'creation'>
len_size := 2.
]
typeKind: aType [
<category: 'creation'>
type := aType
]
typeKind [
<category: 'accessing'>
^ type
]
parseClass: aClass [
<category: 'creation'>
"The class to be used to parse this"
parse_class := aClass
]
parseClass [
<category: 'creation'>
^ parse_class
]
instVarName: aName [
<category: 'creation'>
inst_var := aName
]
instVarName [
<category: 'accessing'>
^ inst_var
]
]
Object subclass: TLVParserBase [
<category: 'OsmoNetwork-TLV'>
<comment: 'I am the base class for TLV like parsers. I provide common
routines for parsing.'>
parseMandatory: attr tag: aTag stream: aStream [
<category: 'parsing'>
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 [
<category: 'parsing'>
^ self parseOptional: attr tag: aTag stream: aStream
]
parseOptional: attr tag: aTag stream: aStream [
<category: 'parsing'>
aTag = attr tag
ifFalse: [^false].
aStream skip: 1.
self doParse: attr stream: aStream.
]
doParse: attr stream: aStream [
<category: 'parsing'>
attr parseClass isNil
ifTrue: [^self error: 'No parse class available'].
self instVarNamed: attr instVarName
put: (attr parseClass readFrom: aStream with: attr).
^ true
]
writeOn: aMsg [
<category: 'serialize'>
"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.
].
]
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
TestCase subclass: TLVDescriptionTest [
<category: 'OsmoNetwork-Tests'>
<comment: 'I try to test the TLV Description'>
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.
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: IPAConstants [
<category: 'OsmoNetwork-IPA'>
<comment: 'I have the constants for the IPA protocol.'>
IPAConstants class >> protocolRSL [ <category: 'constants'> ^ 16r00 ]
IPAConstants class >> protocolMGCP [ <category: 'constants'> ^ 16rFC ]
IPAConstants class >> protocolSCCP [ <category: 'constants'> ^ 16rFD ]
IPAConstants class >> protocolIPA [ <category: 'constants'> ^ 16rFE ]
IPAConstants class >> protocolOML [ <category: 'constants'> ^ 16rFF ]
IPAConstants class >> protocolOSMO [ <category: 'constants'> ^ 16rEE ]
IPAConstants class >> msgPing [ <category: 'constants'> ^ 16r00 ]
IPAConstants class >> msgPong [ <category: 'constants'> ^ 16r01 ]
IPAConstants class >> msgIdGet [ <category: 'constants'> ^ 16r04 ]
IPAConstants class >> msgIdResp [ <category: 'constants'> ^ 16r05 ]
IPAConstants class >> msgIdAck [ <category: 'constants'> ^ 16r06 ]
IPAConstants class >> msgSCCP [ <category: 'constants'> ^ 16rFF ]
IPAConstants class >> idtagSernr [ <category: 'constants'> ^ 16r00 ]
IPAConstants class >> idtagUnitName [ <category: 'constants'> ^ 16r01 ]
IPAConstants class >> idtagLocation1 [ <category: 'constants'> ^ 16r02 ]
IPAConstants class >> idtagLocation2 [ <category: 'constants'> ^ 16r03 ]
IPAConstants class >> idtagEquipVer [ <category: 'constants'> ^ 16r04 ]
IPAConstants class >> idtagSwVersion [ <category: 'constants'> ^ 16r05 ]
IPAConstants class >> idtagIpaddr [ <category: 'constants'> ^ 16r06 ]
IPAConstants class >> idtagMacaddr [ <category: 'constants'> ^ 16r07 ]
IPAConstants class >> idtagUnit [ <category: 'constants'> ^ 16r08 ]
IPAConstants class >> osmoCtrl [ <category: 'osmo-extension-constants'> ^ 16r00 ]
IPAConstants class >> osmoMgcp [ <category: 'osmo-extension-constants'> ^ 16r01 ]
IPAConstants class >> osmoLac [ <category: 'osmo-extension-constants'> ^ 16r02 ]
IPAConstants class >> protocolOsmoCTRL [
<category: 'constants'>
^ {self protocolOSMO. self osmoCtrl}
]
IPAConstants class >> protocolOsmoMGCP [
<category: 'constants'>
^ {self protocolOSMO. self osmoMgcp}
]
IPAConstants class >> protocolOsmoLAC [
<category: 'constants'>
^ {self protocolOSMO. self osmoLac}
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
CCompound subclass: CPackedStruct [
<shape: #word>
<category: 'OsmoNetwork-Core-GST'>
<comment: 'I am a packed struct with one byte alignment,
Paolo created me, Holger copied me here.'>
CPackedStruct class >> declaration: array [
"Compile methods that implement the declaration in array."
<category: 'subclass creation'>
self
declaration: array
inject: self superclass sizeof
into: [:oldOffset :alignment | oldOffset]
]
CPackedStruct class >> compileSize: size align: alignment [
<category: 'private'>
^ super compileSize: size align: 1.
]
]
CPackedStruct subclass: IPASCCPState [
<category: 'OsmoNetwork-IPA'>
<comment: 'This is an Osmocom NAT extension to hand out USSD
to a different provider.'>
<declaration: #(
#(#src (#array #byte 3))
#(#dst (#array #byte 3))
#(#transId #byte)
#(#invokeId #byte)
#(#imsi (#array #char 17))) >
srcAddr [
<category: 'accessing'>
^ SCCPAddrReference fromCData: self src.
]
dstAddr [
<category: 'accessing'>
^ SCCPAddrReference fromCData: self dst.
]
imsiString [
"We will need to count how many chars of the array are used"
<category: 'accessing'>
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.
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: IPADispatcher [
| handlers |
<category: 'OsmoNetwork-IPA'>
<comment: 'I am a hub and one can register handlers for the streams'>
IPADispatcher class >> new [
<category: 'creation'>
^ super new
initialize;
yourself
]
initialize [
<category: 'private'>
handlers := Dictionary new.
]
addHandler: aStream on: anObject with: aSelector [
<category: 'handler'>
handlers at: aStream put: [:msg | anObject perform: aSelector with: msg].
]
addHandler: aStream on: aBlock [
<category: 'handler'>
handlers at: aStream put: aBlock.
]
dispatch: aStream with: aData [
| handler |
<category: 'handler'>
handler := handlers at: aStream ifAbsent: [
self logError: ('IPADispatcher has no registered handler for <1p>'
expandMacrosWith: aStream) area: #ipa.
^ false
].
handler value: aData.
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: IPAMsgRequest [
| data type |
<category: 'OsmoNetwork-IPA'>
<comment: 'I can parse the IPA messages and generate them'>
IPAMsgRequest class >> parse: aStream [
| type data |
<category: 'parsing'>
"TLV parser for the IPAMessage"
type := aStream next.
data := self parseTLV: aStream.
^ self new
type: type;
data: data;
yourself.
]
IPAMsgRequest class >> parseTLV: aStream [
| data |
<category: 'parsing'>
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 [
<category: 'data'>
type := aType.
]
data: aData [
<category: 'data'>
data := aData.
]
tags [
<category: 'accessing'>
^ data collect: [:each | each key].
]
hasTag: aTag [
<category: 'accessing'>
^ self tags includes: aTag
]
dataForTag: aTag [
<category: 'accessing'>
data do: [:each | each key = aTag ifTrue: [^each value]].
^ SystemExceptions.NotFound
signalOn: self what: 'Tag ', aTag asString, ' not found'.
]
writeOn: aMsg [
<category: 'serialize'>
aMsg putByte: type.
self writeTLV: aMsg.
]
writeTLV: aMsg [
<category: 'serialize'>
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 [
<category: 'OsmoNetwork-IPA'>
<comment: 'I can handle messages with a two byte size after the
type and then followed by the usual TV'>
IPAMsgResponse class >> parse: aStream [
| type data |
<category: 'parsing'>
"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 [
<category: 'serialize'>
aMsg putByte: type.
aMsg putByte: 0.
self writeTLV: aMsg.
]
writeTLV: aMsg [
<category: 'serialize'>
"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.
].
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: IPADemuxer [
| socket |
<category: 'OsmoNetwork-IPA'>
<comment: 'I know how to demultiplex data from a socket. Give
me the socket and I read from it and provide you a tuple.'>
IPADemuxer class >> initOn: aSocket [
<category: 'creation'>
^ (self new)
socket: aSocket;
yourself.
]
next [
"Return a tuple of stream and bytearray"
<category: 'reading'>
| 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 [
<category: 'accessing'>
socket := aSocket.
]
]
Object subclass: IPAMuxer [
| socket |
<category: 'OsmoNetwork-IPA'>
<comment: 'I can multiplex data according to the IPA protocol. You
will need to give me a Socket or a SharedQueue and I will mux the
data you provide me with.'>
IPAMuxer class >> initOn: aSocket [
<category: 'creation'>
^ (self new)
socket: aSocket;
yourself.
]
prepareNext: aData with: aStream [
"Write the data onto the stream"
| msg |
<category: 'accessing'>
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 [
<category: 'encoding'>
socket nextPut: (self prepareNext: aData with: aStream).
]
socket: aSocket [
<category: 'accessing'>
socket := aSocket.
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: IPAProtoHandler [
| token muxer |
<comment: 'I can be registered on an IPADispatcher and will
handle the IPA protocol. You can subclass me to change the
behavior.'>
<category: 'OsmoNetwork-IPA'>
IPAProtoHandler class [
| handlers |
initialize [
<category: 'creation'>
^ self initializeHandlers
]
]
IPAProtoHandler class >> initializeHandlers [
<category: 'private'>
(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 [
<category: 'initialize'>
aDispatcher addHandler: IPAConstants protocolIPA on: self with: #handleMsg:.
]
muxer: aMuxer [
<category: 'initialize'>
muxer := aMuxer.
]
token: aToken [
<category: 'authentication'>
token := aToken.
]
handleMsg: aMsg [
| selector |
<category: 'dispatch'>
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 [
<category: 'private'>
muxer nextPut: (ByteArray with: IPAConstants msgPong) with: IPAConstants protocolIPA.
]
handlePong: aMsg [
<category: 'private'>
self logDebug: 'PONG' area: #ipa.
]
handleIdGet: aMsg [
| msg |
<category: 'authentication'>
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 [
<category: 'private'>
self logDebug: 'ID ACK' area: #ipa.
]
]
Eval [
IPAProtoHandler initialize.
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
TestCase subclass: IPATests [
| called |
<category: 'OsmoNetwork-Tests'>
IPATests class >> packageNamesUnderTest [
<category: 'accessing'>
^ #('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 |
<category: 'dispatch-test'>
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 [
<category: 'dispatch-test'>
called := aData = 'data'.
]
]
TestCase subclass: IPAMsgTests [
<category: 'OsmoNetwork-Tests'>
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 [
<category: 'test-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 [
<category: 'OsmoNetwork-Tests'>
testSize [
self assert: IPASCCPState sizeof = 25.
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: ISUPConstants [
<comment: 'Constants for the ISDN User Part (ISUP) protocol'>
<category: 'OsmoNetwork-ISUP'>
ISUPConstants class [
msgAPT [
"Application transport"
<category: 'constants'>
^ 2r01000001
]
msgACM [
"Address complete"
<category: 'constants'> ^ 2r00000110
]
msgAMN [
"Answer"
<category: 'constants'> ^ 2r00001001
]
msgBLA [
"Blocking acknowledgement"
<category: 'constants'> ^ 2r00010101
]
msgBLO [
"Blocking"
<category: 'constants'> ^ 2r00010011
]
msgCCR [
"Continuity check request"
<category: 'constants'> ^ 2r00010001
]
msgCFN [
"Confusion"
<category: 'constants'> ^ 2r00101111
]
msgCGB [
"Circuit group blocking"
<category: 'constants'> ^ 2r00011000
]
msgCGBA [
"Circuit group blocking acknowledgement"
<category: 'constants'> ^ 2r00011010
]
msgCGU [
"Circuit group unblocking"
<category: 'constants'> ^ 2r00011001
]
msgCGUA [
"Circuit group unblocking acknowledgement"
<category: 'constants'> ^ 2r00011011
]
msgCON [
"Connect"
<category: 'constants'> ^ 2r00000111
]
msgCOT [
"Continuity"
<category: 'constants'> ^ 2r00000101
]
msgCPG [
"Call progress"
<category: 'constants'> ^ 2r00101100
]
msgCRG [
"Charge information"
<category: 'constants'> ^ 2r00110001
]
msgCQM [
"Circuit group query"
<category: 'constants'> ^ 2r00101010
]
msgCQR [
"Circuit group query response"
<category: 'constants'> ^ 2r00101011
]
msgDRS [
"Delayed release (reserved used in 1988 version)"
<category: 'constants'> ^ 2r00100111
]
msgFAC [
"Facility"
<category: 'constants'> ^ 2r00110011
]
msgFAA [
"Facility accepted"
<category: 'constants'> ^ 2r00100000
]
msgFAR [
"Facility request"
<category: 'constants'> ^ 2r00011111
]
msgFOT [
"Forward transfer"
<category: 'constants'> ^ 2r00001000
]
msgFRJ [
"Facility reject"
<category: 'constants'> ^ 2r00100001
]
msgGRA [
"Circuit group reset acknowledgement"
<category: 'constants'> ^ 2r00101001
]
msgGRS [
"Circuit group reset"
<category: 'constants'> ^ 2r00010111
]
msgIDR [
"Identification request"
<category: 'constants'> ^ 2r00110110
]
msgIDS [
"Identification response"
<category: 'constants'> ^ 2r00110111
]
msgIAM [
"Initial address"
<category: 'constants'> ^ 2r00000001
]
msgINF [
"Information"
<category: 'constants'> ^ 2r00000100
]
msgINR [
"Information request"
<category: 'constants'> ^ 2r00000011
]
msgLPA [
"Loop back acknowledgement"
<category: 'constants'> ^ 2r00100100
]
msgLPR [
"Loop prevention"
<category: 'constants'> ^ 2r01000000
]
msgOLM [
"Overload"
<category: 'constants'> ^ 2r00110000
]
msgPAM [
"Pass-along"
<category: 'constants'> ^ 2r00101000
]
msgREL [
"Release"
<category: 'constants'> ^ 2r00001100
]
msgRES [
"Resume"
<category: 'constants'> ^ 2r00001110
]
msgRLC [
"Release complete"
<category: 'constants'> ^ 2r00010000
]
msgRSC [
"Reset circuit"
<category: 'constants'> ^ 2r00010010
]
msgSAM [
"Subsequent address"
<category: 'constants'> ^ 2r00000010
]
msgSUS [
"Suspend"
<category: 'constants'> ^ 2r00001101
]
msgUBL [
"Unblocking"
<category: 'constants'> ^ 2r00010100
]
msgUBA [
"Unblocking acknowledgement"
<category: 'constants'> ^ 2r00010110
]
msgUCIC [
"Unequipped circuit identification code"
<category: 'constants'> ^ 2r00101110
]
msgUSR [
"User-to-user information"
<category: 'constants'> ^ 2r00101101
]
msgNRM [
"Network resource management"
<category: 'constants'> ^ 2r00110010
]
msgPRI [
"Pre-release information"
<category: 'constants'> ^ 2r01000010
]
msgSAN [
"Subsequent Directory Number"
<category: 'constants'> ^ 2r01000011
]
msgSEG [
"Segmentation"
<category: 'constants'> ^ 2r00111000
]
msgUPA [
"User Part available"
<category: 'constants'> ^ 2r00110100
]
msgUPT [
"User Part test"
<category: 'constants'> ^ 2r00110100
]
parAccessDeliveryInformation [ <category: 'constants-Q767'> ^ 2r00101110 ]
parAccessTransport [ <category: 'constants-Q767'> ^ 2r00000011 ]
parApplicationTransportParameter [ <category: 'constants-Q767'> ^ 2r01111000 ]
parAutomaticCongestionLevel [ <category: 'constants-Q767'> ^ 2r00100111 ]
parBackwardCallIndicators [ <category: 'constants-Q767'> ^ 2r00010001 ]
parBackwardGVNS [ <category: 'constants-Q767'> ^ 2r01001101 ]
parCallDiversionInformation [ <category: 'constants-Q767'> ^ 2r00110110 ]
parCallDiversionTreatmentIndicators [ <category: 'constants-Q767'> ^ 2r01101110 ]
parCallHistoryInformation [ <category: 'constants-Q767'> ^ 2r00101101 ]
parCallOfferingTreatmentIndicators [ <category: 'constants-Q767'> ^ 2r01110000 ]
parCallReference [ <category: 'constants-Q767'> ^ 2r00000001 ]
parCallTransferNumber [ <category: 'constants-Q767'> ^ 2r01000101 ]
parCallTransferReference [ <category: 'constants-Q767'> ^ 2r01000011 ]
parCalledINNumber [ <category: 'constants-Q767'> ^ 2r01101111 ]
parCalledDirectoryNumber [ <category: 'constants-Q767'> ^ 2r01111101 ]
parCalledPartyNumber [ <category: 'constants-Q767'> ^ 2r00000100 ]
parCallingGeodeticLocation [ <category: 'constants-Q767'> ^ 2r10000001 ]
parCallingPartyNumber [ <category: 'constants-Q767'> ^ 2r00001010 ]
parCallingPartysCategory [ <category: 'constants-Q767'> ^ 2r00001001 ]
parCauseIndicators [ <category: 'constants-Q767'> ^ 2r00010010 ]
parCCNRPossibleIndicator [ <category: 'constants-Q767'> ^ 2r01111010 ]
parCCSS [ <category: 'constants-Q767'> ^ 2r01001011 ]
parChargedPartyIdentification [ <category: 'constants-Q767'> ^ 2r01110001 ]
parCircuitAssignmentMap [ <category: 'constants-Q767'> ^ 2r00100101 ]
parCircuitGroupSupervisionMessageType [ <category: 'constants-Q767'> ^ 2r00010101 ]
parCircuitStateIndicator [ <category: 'constants-Q767'> ^ 2r00100110 ]
parClosedUserGroupInterlockCode [ <category: 'constants-Q767'> ^ 2r00011010 ]
parCollectCallRequest [ <category: 'constants-Q767'> ^ 2r01111001 ]
parConferenceTreatmentIndicators [ <category: 'constants-Q767'> ^ 2r01110010 ]
parConnectedNumber [ <category: 'constants-Q767'> ^ 2r00100001 ]
parConnectionRequest [ <category: 'constants-Q767'> ^ 2r00001101 ]
parContinuityIndicators [ <category: 'constants-Q767'> ^ 2r00010000 ]
parCorrelationId [ <category: 'constants-Q767'> ^ 2r01100101 ]
parDisplayInformation [ <category: 'constants-Q767'> ^ 2r01110011 ]
parEchoControlInformation [ <category: 'constants-Q767'> ^ 2r00110111 ]
parEndOfOptionalParameters [ <category: 'constants-Q767'> ^ 2r00000000 ]
parEventInformation [ <category: 'constants-Q767'> ^ 2r00100100 ]
parFacilityIndicator [ <category: 'constants-Q767'> ^ 2r00011000 ]
parForwardCallIndicators [ <category: 'constants-Q767'> ^ 2r00000111 ]
parForwardGVNS [ <category: 'constants-Q767'> ^ 2r01001100 ]
parGenericDigits [ <category: 'constants-Q767'> ^ 2r11000001 ]
parGenericNotificationIndicator [ <category: 'constants-Q767'> ^ 2r00101100 ]
parGenericNumber [ <category: 'constants-Q767'> ^ 2r11000000 ]
parGenericReference [ <category: 'constants-Q767'> ^ 2r10000010 ]
parHTRInformation [ <category: 'constants-Q767'> ^ 2r10000010 ]
parHopCounter [ <category: 'constants-Q767'> ^ 2r00111101 ]
parInformationIndicators [ <category: 'constants-Q767'> ^ 2r00001111 ]
parInformationRequestIndicators [ <category: 'constants-Q767'> ^ 2r00001110 ]
parLocationNumber [ <category: 'constants-Q767'> ^ 2r00111111 ]
parLoopPreventionIndicators [ <category: 'constants-Q767'> ^ 2r01000100 ]
parMCIDRequestIndicators [ <category: 'constants-Q767'> ^ 2r00111011 ]
parMCIDResponseIndicators [ <category: 'constants-Q767'> ^ 2r00111100 ]
parMessageCompatibilityInformation [ <category: 'constants-Q767'> ^ 2r00111000 ]
parMLPPPrecedence [ <category: 'constants-Q767'> ^ 2r00111010 ]
parNatureOfConnectionIndicators [ <category: 'constants-Q767'> ^ 2r00000110 ]
parNetworkManagementControls [ <category: 'constants-Q767'> ^ 2r01011011 ]
parNetworkRoutingNumber [ <category: 'constants-Q767'> ^ 2r10000100 ]
parNetworkSpecificFacility [ <category: 'constants-Q767'> ^ 2r00101111 ]
parNumberPortabilityForwardInformation [ <category: 'constants-Q767'> ^ 2r10001101 ]
parOptionalBackwardCallIndicators [ <category: 'constants-Q767'> ^ 2r00101001 ]
parOptionalForwardCallIndicators [ <category: 'constants-Q767'> ^ 2r00001000 ]
parOriginalCalledNumber [ <category: 'constants-Q767'> ^ 2r00101000 ]
parOriginalCalledINNumber [ <category: 'constants-Q767'> ^ 2r01111111 ]
parOriginationISCPointCode [ <category: 'constants-Q767'> ^ 2r00101011 ]
parParameterCompatibilityInformation [ <category: 'constants-Q767'> ^ 2r00111001 ]
parPivotCapability [ <category: 'constants-Q767'> ^ 2r01111011 ]
parPivotCounter [ <category: 'constants-Q767'> ^ 2r10000111 ]
parPivotRoutingBackwardInformation [ <category: 'constants-Q767'> ^ 2r10001001 ]
parPivotRoutingForwardInformation [ <category: 'constants-Q767'> ^ 2r10001000 ]
parPivotRoutingIndicators [ <category: 'constants-Q767'> ^ 2r01111100 ]
parPivotStatus [ <category: 'constants-Q767'> ^ 2r10000110 ]
parPropagationDelayCounter [ <category: 'constants-Q767'> ^ 2r00110001 ]
parQoRCapability [ <category: 'constants-Q767'> ^ 2r10000101 ]
parRange [ <category: 'constants-Q767'> ^ 2r00010110 ]
parRangeAndStatus [ <category: 'constants-Q767'> ^ 2r00010110 ]
parRedirectBackwardInformation [ <category: 'constants-Q767'> ^ 2r10001100 ]
parRedirectCapability [ <category: 'constants-Q767'> ^ 2r01001110 ]
parRedirectCounter [ <category: 'constants-Q767'> ^ 2r01110111 ]
parRedirectForwardInformation [ <category: 'constants-Q767'> ^ 2r10001011 ]
parRedirectStatus [ <category: 'constants-Q767'> ^ 2r10001010 ]
parRedirectingNumber [ <category: 'constants-Q767'> ^ 2r00001011 ]
parRedirectionInformation [ <category: 'constants-Q767'> ^ 2r00010011 ]
parRedirectionNumber [ <category: 'constants-Q767'> ^ 2r00001100 ]
parRedirectionNumberRestriction [ <category: 'constants-Q767'> ^ 2r01000000 ]
parRemoteOperations [ <category: 'constants-Q767'> ^ 2r00110010 ]
parSCFId [ <category: 'constants-Q767'> ^ 2r01100110 ]
parServiceActivation [ <category: 'constants-Q767'> ^ 2r00110011 ]
parSignallingPointCode [ <category: 'constants-Q767'> ^ 2r00011110 ]
parSubsequentNumber [ <category: 'constants-Q767'> ^ 2r00000101 ]
parSuspendResumeIndicators [ <category: 'constants-Q767'> ^ 2r00100010 ]
parTransitNetworkSelection [ <category: 'constants-Q767'> ^ 2r00100011 ]
parTransmissionMediumRequirement [ <category: 'constants-Q767'> ^ 2r00000010 ]
parTransmissionMediumRequirementPrime [ <category: 'constants-Q767'> ^ 2r00111110 ]
parTransmissionMediumUsed [ <category: 'constants-Q767'> ^ 2r00110101 ]
parUIDActionIndicators [ <category: 'constants-Q767'> ^ 2r01110100 ]
parUIDCapabilityIndicators [ <category: 'constants-Q767'> ^ 2r01110101 ]
parUserServiceInformation [ <category: 'constants-Q767'> ^ 2r00011101 ]
parUserServiceInformationPrime [ <category: 'constants-Q767'> ^ 2r00110000 ]
parUserTeleserviceInformation [ <category: 'constants-Q767'> ^ 2r00110100 ]
parUserToUserIndicators [ <category: 'constants-Q767'> ^ 2r00101010 ]
parUserToUserInformation [ <category: 'constants-Q767'> ^ 2r00100000 ]
addrNAT_NATIONAL [
"National (significant) number"
<category: 'constants-address'>
^ 2r0000011
]
addrNAT_INTERNATIONAL [
"International number"
<category: 'constants-address'>
^ 2r0000100
]
]
]
TLVDescriptionContainer subclass: ISUPMessage [
<comment: 'I am the base class for the ISUP messages'>
<category: 'OsmoNetwork-ISUP'>
ISUPMessage class >> decodeByteStream: aStream [
<category: 'parsing'>
| 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 [
<category: 'encoding'>
| 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 [
<category: 'parsing'>
| 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."
<category: 'parsing'>
| pos ptr |
pos := aStream position.
ptr := aStream next.
aStream skip: ptr - 1.
]
writeVariableEnd: aStream state: aState [
<category: 'encoding'>
"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"
<category: 'encoding'>
"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."
<category: 'encoding'>
^ Dictionary from: {'data' -> (WriteStream on: (ByteArray new: 3))}.
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
ISUPNatureOfConnectionIndicators class extend [
satNoSat [ <category: 'isup-extension'> ^ 2r00 ]
satOneSat [ <category: 'isup-extension'> ^ 2r01 ]
satTwoSat [ <category: 'isup-extension'> ^ 2r10 ]
satSpare [ <category: 'isup-extension'> ^ 2r11 ]
cciNotRequired [ <category: 'isup-extension'> ^ 2r00 ]
cciRequired [ <category: 'isup-extension'> ^ 2r01 ]
cciPerformed [ <category: 'isup-extension'> ^ 2r10 ]
cciSpare [ <category: 'isup-extension'> ^ 2r11 ]
ecdiNotIncluded [ <category: 'isup-extension'> ^ 2r0 ]
ecdiIncluded [ <category: 'isup-extension'> ^ 2r1 ]
]
ISUPCallingPartysCategory class extend [
callingSubscriberWithPriority [
<category: 'encoding'>
^2r1011
]
categoryUnknown [
<category: 'encoding'>
^2r0
]
dataCall [
<category: 'encoding'>
^2r1100
]
operatorLanguageEnglish [
<category: 'encoding'>
^2r10
]
operatorLanguageFrench [
<category: 'encoding'>
^2r1
]
operatorLanguageGerman [
<category: 'encoding'>
^2r11
]
operatorLanguageRussian [
<category: 'encoding'>
^2r100
]
operatorLanguageSpanish [
<category: 'encoding'>
^2r101
]
ordinarySubscriber [
<category: 'encoding'>
^2r1010
]
payphone [
<category: 'encoding'>
^2r1111
]
reserved [
<category: 'encoding'>
^2r1001
]
spare [
<category: 'encoding'>
^2r1110
]
testCall [
<category: 'encoding'>
^2r1101
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
TestCase subclass: ISUPGeneratedTest [
<category: 'OsmoNetwork-Tests'>
<comment: 'I was written on a flight to Taipei. I will try to
instantiate all generated class and walk the hierachy to see if
there are any DNUs'>
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]].
]
]

View File

@ -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

View File

@ -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

View File

@ -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

View File

@ -0,0 +1 @@
Message type 2.1 F 1

View File

@ -0,0 +1,3 @@
Message type 2.1 F 1
Cause indicators 3.12 V 3-?
End of optional parameters 3.20 O 1

View File

@ -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

View File

@ -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

View File

@ -0,0 +1,2 @@
Message type 2.1 F 1
Continuity indicators 3.18 F 1

View File

@ -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

View File

@ -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

View File

@ -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 [ <category: ''field''> ^ 0 ]
' % {aDef className}.
].
aDef className = 'ISUPMessageType'
ifTrue: [^self].
type :=
'MSGFixedField subclass: %1 [
<category: ''OsmoNetwork-ISUP''>
<comment: ''I am an auto generated ISUP fixed field.''>
%1 class >> parameterName [ <category: ''field''> ^ ''%2'' ]
%1 class >> parameterValue [ <category: ''field''> ^ ISUPConstants par%3 ]
%1 class >> octalLength [ <category: ''field''> ^ %4 ]
%1 class >> spec [ <category: ''field''> ^ ''%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 [
<category: ''OsmoNetwork-ISUP''>
<comment: ''I am an auto generated ISUP variable.''>
%1 class >> parameterName [ <category: ''field''> ^ ''%2'' ]
%1 class >> parameterValue [ <category: ''field''> ^ ISUPConstants par%3 ]
%1 class >> octalLength [ <category: ''field''> ^ %4 ]
%1 class >> maxLength [ <category: ''field''> ^ %5 ]
%1 class >> spec [ <category: ''field''> ^ ''%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 [
<category: ''OsmoNetwork-ISUP''>
<comment: ''I am auto-generated ISUP message.''>
ISUP%1 class >> tlvDescription [
<category: ''field''>
^ (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 |
<comment: 'I will create subclasses for identical structs but with a different
message type.'>
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 [
<category: ''OsmoNetwork-ISUP''>
<comment: ''I am an auto generated ISUP message.''>
ISUP%2 class >> tlvDescription [
<category: ''field''>
^ (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.]
]

View File

@ -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

View File

@ -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

View File

@ -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

View File

@ -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

View File

@ -0,0 +1,2 @@
Message type 2.1 F 1
Range and status 3.43 V 3-34

View File

@ -0,0 +1,2 @@
Message type 2.1 F 1
Range 3.43b V 2

View File

@ -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

View File

@ -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

View File

@ -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

View File

@ -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

View File

@ -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

View File

@ -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

View File

@ -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

View File

@ -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

View File

@ -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

View File

@ -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

View File

@ -0,0 +1,3 @@
Message type 2.1 F 1
Cause indicators 3.12 O 4-?
End of optional parameters 3.20 O 1

View File

@ -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

View File

@ -0,0 +1 @@
sameas: blo

View File

@ -0,0 +1 @@
sameas: blo

View File

@ -0,0 +1 @@
sameas: cgb

View File

@ -0,0 +1 @@
sameas: cgb

View File

@ -0,0 +1 @@
sameas: cgb

View File

@ -0,0 +1 @@
sameas: faa

View File

@ -0,0 +1 @@
sameas: grs

View File

@ -0,0 +1 @@
sameas: blo

View File

@ -0,0 +1 @@
sameas: blo

View File

@ -0,0 +1 @@
sameas: blo

View File

@ -0,0 +1 @@
sameas: res

View File

@ -0,0 +1 @@
sameas: blo

View File

@ -0,0 +1 @@
sameas: blo

View File

@ -0,0 +1 @@
sameas: blo

View File

@ -0,0 +1 @@
sameas: upt

View File

@ -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

View File

@ -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

View File

@ -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

View File

@ -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

File diff suppressed because it is too large Load Diff

View File

@ -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 <http://www.gnu.org/licenses/>.
"
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 |
<category: 'OsmoNetwork-M2UA'>
<comment: 'I am a M2UA Application Server Process.
I have an internal state machine and a state and will be used by the
M2UA Layer. I am written for the usage in a Media Gateway Controller
and will also keep information about the Application Server itself.
If I need to be used on a Signalling Gateway (SG) I will need a dedicated
M2UA Application Server class and state machine.
I can currently only manage a single interface. The specification allows
a single ASP to send one ASPActive for one interface at a time.'>
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."
<category: 'Primitives-LayerManagement'>
error_block := aBlock
]
onNotify: aBlock [
"M-NOTIFY indication
Direction: M2UA -> LM
Purpose: ASP reports that it has received a NOTIFY message
from its peer."
<category: 'Primitives-LayerManagement'>
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."
<category: 'Primitives-LayerManagement-SCTP'>
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."
<category: 'Primitives-LayerManagement-SCTP'>
sctp_released_block := aBlock
]
onSctpRestarted: aBlock [
"M-SCTP_RELEASE indication
Direction: M2UA -> LM
Purpose: SGP informs LM that ASP has released an SCTP association."
<category: 'Primitives-LayerManagement-SCTP'>
sctp_restarted_block := aBlock
]
onSctpStatus: aBlock [
"M-SCTP_STATUS indication
Direction: M2UA -> LM
Purpose: M2UA reports status of SCTP association."
<category: 'Primitives-LayerManagement-SCTP'>
sctp_status_block := aBlock
]
sctpEstablish [
"M-SCTP_ESTABLISH request
Direction: LM -> M2UA
Purpose: LM requests ASP to establish an SCTP association with an SGP."
<category: 'Primitives-LayerManagement-SCTP'>
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."
<category: 'Primitives-LayerManagement-SCTP'>
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."
<category: 'Primitives-LayerManagement-SCTP'>
self notYetImplemented
]
aspActive [
<category: 'Primitives-LayerManagemennt-ASP'>
"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 [
<category: 'Primitives-LayerManagemennt-ASP'>
"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 [
<category: 'Primitives-LayerManagemennt-ASP'>
"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 [
<category: 'Primitives-LayerManagemennt-ASP'>
"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."
<category: 'Primitives-LayerManagemennt-ASP'>
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."
<category: 'Primitives-LayerManagemennt-ASP'>
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."
<category: 'Primitives-LayerManagemennt-ASP'>
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."
<category: 'Primitives-LayerManagemennt-ASP'>
asp_up_block := aBlock
]
onStateChange: aBlock [
"A generic callback for all state changes"
<category: 'Primitives-LayerManagemennt-ASP'>
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."
<category: 'Primitives-LayerManagement-LinkKey'>
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."
<category: 'Primitives-LayerManagement-LinkKey'>
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."
<category: 'Primitives-LayerManagement-LinkKey'>
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."
<category: 'Primitives-LayerManagement-LinkKey'>
self notYetImplemented
]
hostname: aHostname port: aPort [
"Select the SCTP hostname/port for the SG to connect to"
<category: 'configuration'>
socket
hostname: aHostname;
port: aPort
]
createAspIdentTag [
<category: 'm2ua-tags'>
^M2UATag initWith: M2UAConstants tagAspIdent data: #(1 2 3 4)
]
createIdentIntTag [
<category: 'm2ua-tags'>
^M2UATag initWith: M2UAConstants tagIdentInt data: #(0 0 0 0)
]
createInfoTag [
<category: 'm2ua-tags'>
^M2UATag initWith: M2UAConstants tagInfo
data: 'Hello from Smalltalk' asByteArray
]
callNotification: aBlock [
"Inform the generic method first, then all the others"
<category: 'private'>
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:"
<category: 'private'>
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 [
<category: 'private'>
| msg |
msg := M2UAMSG parseToClass: aByteArray.
msg dispatchOnAsp: self
]
dispatchNotification: aBlock [
<category: 'private'>
aBlock value
]
internalReset [
<category: 'private'>
self socketService: socket
]
moveToState: newState [
<category: 'private'>
((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 [
<category: 'private'>
"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."
<category: 'private'>
self moveToState: M2UAAspStateDown.
established = true ifFalse: [^self].
sctp_released_block ifNotNil: [sctp_released_block value]
]
send: aMsg [
"Forget about what we did before"
<category: 'private'>
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 [
<category: 'creation'>
state := M2UAAspStateDown
]
socketService: aService [
<category: 'creation'>
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 [
<category: 'dispatch'>
t_ack cancel.
self moveToState: M2UAAspStateActive.
self callNotification: asp_active_block
]
handleAspDownAck: aMsg [
<category: 'dispatch'>
t_ack cancel.
as_state := nil.
self moveToState: M2UAAspStateDown.
self callNotification: asp_down_block
]
handleAspInactiveAck: aMsg [
<category: 'dispatch'>
t_ack cancel.
as_state := nil.
self moveToState: M2UAAspStateInactive.
self callNotification: asp_inactive_block
]
handleAspUpAck: aMsg [
<category: 'dispatch'>
t_ack cancel.
self moveToState: M2UAAspStateInactive.
self callNotification: asp_inactive_block
]
handleError: aMsg [
"Cancel pending operations.. because something went wrong"
<category: 'dispatch'>
t_ack cancel.
error_block ifNotNil: [error_block value: aMsg]
]
handleNotify: aMsg [
<category: 'dispatch'>
"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."
<category: 'dispatch'>
]
isASActive [
<category: 'status'>
^as_state = M2UAConstants ntfyStateASActive
]
isASInactive [
<category: 'status'>
^as_state = M2UAConstants ntfyStateASInactive
]
isASPending [
<category: 'status'>
^as_state = M2UAConstants ntfyStateASPending
]
state [
<category: 'accessing'>
^state
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: M2UAAspStateMachine [
| state |
<category: 'OsmoNetwork-M2UA-States'>
<comment: 'I am the Application Server Process State machine. An
pplication Server Process will create me to manage the state. My state
machine is driven by calling the selectors from the events protocol.
If you ask for an illegal state transition a DNU will be raised. Ath
this point you should probably reset what you are doing and do proper
error reporting.
This class is currently not used!'>
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 [
<category: 'events'>
state onAspActive: anEvent
]
aspDown: anEvent [
<category: 'events'>
state onAspDown: anEvent
]
aspInactive: anEvent [
<category: 'events'>
state onAspInactive: anEvent
]
aspUp: anEvent [
<category: 'events'>
state onAspUp: anEvent
]
otherAspInAsOverrides: anEvent [
<category: 'events'>
state onOtherAspInAsOverrides: anEvent
]
sctpCdi: anEvent [
<category: 'events'>
state onSctpCdi: anEvent
]
sctpRi: anEvent [
<category: 'events'>
state onSctpRi: anEvent
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
UAConstants subclass: M2UAConstants [
<category: 'OsmoNetwork-M2UA'>
<comment: 'I hold the M2UA specific constants'>
M2UAConstants class >> version [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> spare [ <category: 'constants'> ^ 0 ]
M2UAConstants class >> tagData [ <category: 'constants'> ^ 768 ]
M2UAConstants class >> tagDataTTC [ <category: 'constants'> ^ 769 ]
M2UAConstants class >> tagStateReq [ <category: 'constants'> ^ 770 ]
M2UAConstants class >> tagStateEvent [ <category: 'constants'> ^ 771 ]
M2UAConstants class >> tagCongStatus [ <category: 'constants'> ^ 772 ]
M2UAConstants class >> tagDiscStatus [ <category: 'constants'> ^ 773 ]
M2UAConstants class >> tagAction [ <category: 'constants'> ^ 774 ]
M2UAConstants class >> tagSeqNo [ <category: 'constants'> ^ 775 ]
M2UAConstants class >> tagRetrRes [ <category: 'constants'> ^ 776 ]
M2UAConstants class >> tagLinkKey [ <category: 'constants'> ^ 777 ]
M2UAConstants class >> tagLocLinkeyIdent [ <category: 'constants'> ^ 778 ]
M2UAConstants class >> tagSDT [ <category: 'constants'> ^ 779 ]
M2UAConstants class >> tagSDL [ <category: 'constants'> ^ 780 ]
M2UAConstants class >> tagRegRes [ <category: 'constants'> ^ 781 ]
M2UAConstants class >> tagRegStatus [ <category: 'constants'> ^ 782 ]
M2UAConstants class >> tagDeregRes [ <category: 'constants'> ^ 783 ]
M2UAConstants class >> tagDeregStatus [ <category: 'constants'> ^ 784 ]
M2UAConstants class >> statusLpoSet [ <category: 'constants'> ^ 0 ]
M2UAConstants class >> statusLpoClear [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> statusEmergSet [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> statusEmergClear [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> statusFlushBufs [ <category: 'constants'> ^ 4 ]
M2UAConstants class >> statusContinue [ <category: 'constants'> ^ 5 ]
M2UAConstants class >> statusClearRTB [ <category: 'constants'> ^ 6 ]
M2UAConstants class >> statusAudit [ <category: 'constants'> ^ 7 ]
M2UAConstants class >> statusCongCleared[ <category: 'constants'> ^ 8 ]
M2UAConstants class >> statusCongAccept [ <category: 'constants'> ^ 9 ]
M2UAConstants class >> statusCongDisc [ <category: 'constants'> ^ 10 ]
M2UAConstants class >> eventRPOEnter [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> eventRPOExit [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> eventLPOEnter [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> eventLPOExit [ <category: 'constants'> ^ 4 ]
M2UAConstants class >> congLevelNone [ <category: 'constants'> ^ 0 ]
M2UAConstants class >> congLevel1 [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> congLevel2 [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> congLevel3 [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> actionRtrvBSN [ <category: 'constants'> ^ 0 ]
M2UAConstants class >> actionRtrvMSGs [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> resultSuccess [ <category: 'constants'> ^ 0 ]
M2UAConstants class >> resultFailure [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> traOverride [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> traLoadShare [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> traBroadcast [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> errInvalidVersion [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> errInvalidIdent [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> errUnsMsgClass [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> errUnsMsgType [ <category: 'constants'> ^ 4 ]
M2UAConstants class >> errUnsTraMode [ <category: 'constants'> ^ 5 ]
M2UAConstants class >> errUneMsg [ <category: 'constants'> ^ 6 ]
M2UAConstants class >> errProtocolError [ <category: 'constants'> ^ 7 ]
M2UAConstants class >> errUnsInterIdentInt [ <category: 'constants'> ^ 8 ]
M2UAConstants class >> errInvalidStreamIdent[ <category: 'constants'> ^ 9 ]
M2UAConstants class >> errUnsued1 [ <category: 'constants'> ^ 10 ]
M2UAConstants class >> errUnsued2 [ <category: 'constants'> ^ 11 ]
M2UAConstants class >> errUnsued3 [ <category: 'constants'> ^ 12 ]
M2UAConstants class >> errRefused [ <category: 'constants'> ^ 13 ]
M2UAConstants class >> errAspIdentRequired [ <category: 'constants'> ^ 14 ]
M2UAConstants class >> errInvalidAspIdent [ <category: 'constants'> ^ 15 ]
M2UAConstants class >> errAspActForIdent [ <category: 'constants'> ^ 16 ]
M2UAConstants class >> errInvalidParamVal [ <category: 'constants'> ^ 17 ]
M2UAConstants class >> errParamFieldError [ <category: 'constants'> ^ 18 ]
M2UAConstants class >> errUnexpParam [ <category: 'constants'> ^ 19 ]
M2UAConstants class >> errUnused4 [ <category: 'constants'> ^ 20 ]
M2UAConstants class >> errUnused5 [ <category: 'constants'> ^ 21 ]
M2UAConstants class >> errMissingParam [ <category: 'constants'> ^ 22 ]
M2UAConstants class >> ntfyKindStateChange [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> ntfyKindOther [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> ntfyStateASInactive [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> ntfyStateASActive [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> ntfyStateASPending [ <category: 'constants'> ^ 4 ]
M2UAConstants class >> ntfyOtherInsuffRes [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> ntfyOtherAltAspActiv [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> ntfyOtherAspFailure [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> regSuccess [ <category: 'constants'> ^ 0 ]
M2UAConstants class >> regErrorUnknown [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> regErrorInvSDLI [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> regErrorInvSDTI [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> regErrorInvLinkKey [ <category: 'constants'> ^ 4 ]
M2UAConstants class >> regErrorPermDenied [ <category: 'constants'> ^ 5 ]
M2UAConstants class >> regErrorOverlapKey [ <category: 'constants'> ^ 6 ]
M2UAConstants class >> regErrorNotProvisioned [ <category: 'constants'> ^ 7 ]
M2UAConstants class >> regErrorInsuffRes [ <category: 'constants'> ^ 8 ]
M2UAConstants class >> deregSuccess [ <category: 'constants'> ^ 0 ]
M2UAConstants class >> deregErrorUnknown [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> deregErrorInvIdent [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> deregErrorPermDenied [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> deregErrorNotReg [ <category: 'constants'> ^ 4 ]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: M2UAExamples [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
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
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: M2UALayerManagement [
| targetState managedProcess |
<category: 'OsmoNetwork-M2UA'>
<comment: 'I am taking the LayerManagement control for an M2UAApplicationServiceProcess.
Currently you can tell me the ASP state this class should be in
and I will react to to the events from the ASP.'>
applicationServerProcess: aProcess [
<category: 'creation'>
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."
<category: 'creation'>
managedProcess
sctpRelease;
sctpEstablish
]
targetState: aState [
"Use the M2UAAspState subclasses for the states"
<category: 'creation'>
targetState := aState
]
applicationServerProcess [
<category: 'accessing'>
^managedProcess
]
m2uaActive [
"E.g if the target state is already reached"
<category: 'as-process-callbacks'>
managedProcess state = targetState ifTrue: [^self targetReached].
targetState = M2UAAspStateInactive
ifTrue: [managedProcess aspInactive]
ifFalse: [managedProcess aspDown]
]
m2uaDown [
"E.g if the target state is already reached"
<category: 'as-process-callbacks'>
managedProcess state = targetState ifTrue: [^self targetReached].
"There is only one way forward"
managedProcess aspUp
]
m2uaError: aMsg [
<category: 'as-process-callbacks'>
self logNotice: 'M2UA Error.' area: #m2ua
]
m2uaInactive [
"E.g if the target state is already reached"
<category: 'as-process-callbacks'>
managedProcess state = targetState ifTrue: [^self targetReached].
targetState = M2UAAspStateActive
ifTrue: [managedProcess aspActive]
ifFalse: [managedProcess aspDown]
]
m2uaNotify: type ident: ident [
"TODO: Check the type/ident"
<category: 'as-process-callbacks'>
]
m2uaUp [
"E.g if the target state is already reached"
<category: 'as-process-callbacks'>
managedProcess state = targetState ifTrue: [^self targetReached].
targetState = M2UAAspStateActive
ifTrue: [managedProcess aspActive]
ifFalse: [managedProcess aspInactive]
]
sctpEstablished [
"E.g if the target state is already reached"
<category: 'as-process-callbacks'>
managedProcess state = targetState ifTrue: [^self].
"There is only one way forward"
managedProcess aspUp
]
targetReached [
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: M2UAMSG [
| msg_class msg_type tags |
<category: 'OsmoNetwork-M2UA'>
<comment: 'I can parse a M2UA message from the wire, allow you
to see the class, type and include tags. In C the structure will
look like this:
struct m2ua_common_hdr {
uint8_t version;
uint8_t spare;
uint8_t msg_class;
uint8_t msg_type;
uint32_t msg_length;
uint8_t data[0];
} __attribute__((packed));
struct m2ua_parameter_hdr {
uint16_t tag;
uint16_t len;
uint8_t data[0];
} __attribute__((packed));
'>
M2UAMSG class >> parseFrom: aMsg [
<category: 'parsing'>
self logDataContext: aMsg area: #m2ua.
^ self new
parseFrom: aMsg readStream;
yourself.
]
M2UAMSG class >> fromClass: aClass type: aType [
<category: 'parsing'>
^ self new
instVarNamed: #msg_class put: aClass;
instVarNamed: #msg_type put: aType;
yourself.
]
M2UAMSG class >> copyFromOtherMessage: aMsg [
<category: 'parsing'>
^ self new
msgClass: aMsg msgClass;
msgType: aMsg msgType;
tags: aMsg tags;
yourself
]
M2UAMSG class >> parseToClass: aMsg [
<category: 'parsing'>
"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 [
<category: 'accessing'>
^ msg_class
]
msgType [
<category: 'accessing'>
^ msg_type
]
findTag: aTag [
"I find a tag with a tag identifier"
<category: 'accessing'>
^self findTag: aTag ifAbsent: [nil]
]
findTag: aTag ifAbsent: aBlock [
"I find a tag with a tag identifier"
<category: 'accessing'>
self tags do: [:each |
(each isTag: aTag) ifTrue: [
^ each
]
].
^ aBlock value
]
tags [
<category: 'private'>
^ tags ifNil: [tags := OrderedCollection new]
]
parseFrom: aStream [
<category: 'parsing'>
| 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 [
<category: 'parsing'>
| 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 [
<category: 'parsing'>
| 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 [
<category: 'parsing'>
tags := OrderedCollection new.
[aStream position < end]
whileTrue: [tags add: (M2UATag fromStream: aStream)].
^tags
]
parseVersion: aStream [
<category: 'parsing'>
| 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 [
<category: 'encoding'>
self tags add: aTag.
]
writeOn: aMsg [
| tag_data |
<category: 'private'>
"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 [
<category: 'creation'>
msg_class := aClass
]
msgClass: aClass [
<category: 'creation'>
self class: aClass
]
msgType: aType [
<category: 'creation'>
msg_type := aType
]
tags: aTags [
<category: 'creation'>
tags := aTags
]
dispatchOnAsp: anAsp [
<category: 'm2ua-asp-dispatch'>
anAsp handleUnknownMessage: self
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
M2UAMSG subclass: M2UAASPSMMessage [
<category: 'OsmoNetwork-M2UA'>
<comment: 'Application Server Process State Maintenance (ASPSM) messages'>
M2UAASPSMMessage class >> messageClass [
^M2UAConstants clsASPSM
]
]
M2UAMSG subclass: M2UAASPTMMessage [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
M2UAASPTMMessage class >> messageClass [
^M2UAConstants clsASPTM
]
]
M2UAMSG subclass: M2UAASPMGMTMessage [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
M2UAASPMGMTMessage class >> messageClass [
^M2UAConstants clsMgmt
]
]
M2UAASPSMMessage subclass: M2UAApplicationServerProcessHeartbeatAck [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
M2UAApplicationServerProcessHeartbeatAck class >> messageTag [
^M2UAConstants aspsmBeatAck
]
]
M2UAASPSMMessage subclass: M2UAApplicationServerProcessDown [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
M2UAApplicationServerProcessDown class >> messageTag [
^M2UAConstants aspsmDown
]
dispatchOnAsp: anAsp [
<category: 'm2ua-asp-dispatch'>
anAsp handleAspDown: self
]
]
M2UAASPSMMessage subclass: M2UAApplicationServerProcessHeartbeat [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
M2UAApplicationServerProcessHeartbeat class >> messageTag [
^M2UAConstants aspsmBeat
]
]
M2UAASPSMMessage subclass: M2UAApplicationServerProcessDownAck [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
M2UAApplicationServerProcessDownAck class >> messageTag [
^M2UAConstants aspsmDownAck
]
dispatchOnAsp: anAsp [
<category: 'm2ua-asp-dispatch'>
anAsp handleAspDownAck: self
]
]
M2UAASPSMMessage subclass: M2UAApplicationServerProcessUp [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
M2UAApplicationServerProcessUp class >> messageTag [
^M2UAConstants aspsmUp
]
dispatchOnAsp: anAsp [
<category: 'm2ua-asp-dispatch'>
anAsp handleAspUp: self
]
]
M2UAASPTMMessage subclass: M2UAApplicationServerProcessInactiveAck [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
M2UAApplicationServerProcessInactiveAck class >> messageTag [
^M2UAConstants asptmInactivAck
]
dispatchOnAsp: anAsp [
<category: 'm2ua-asp-dispatch'>
anAsp handleAspInactiveAck: self
]
]
M2UAASPTMMessage subclass: M2UAApplicationServerProcessActive [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
M2UAApplicationServerProcessActive class >> messageTag [
^M2UAConstants asptmActiv
]
dispatchOnAsp: anAsp [
<category: 'm2ua-asp-dispatch'>
anAsp handleAspActive: self
]
]
M2UAASPTMMessage subclass: M2UAApplicationServerProcessInactive [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
M2UAApplicationServerProcessInactive class >> messageTag [
^M2UAConstants asptmInactiv
]
dispatchOnAsp: anAsp [
<category: 'm2ua-asp-dispatch'>
anAsp handleAspInactive: self
]
]
M2UAASPMGMTMessage subclass: M2UAApplicationServerProcessNotify [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
M2UAApplicationServerProcessNotify class >> messageTag [
^M2UAConstants mgmtNtfy
]
dispatchOnAsp: anAsp [
<category: 'm2ua-asp-dispatch'>
anAsp handleNotify: self
]
]
M2UAASPMGMTMessage subclass: M2UAApplicationServerProcessError [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
M2UAApplicationServerProcessError class >> messageTag [
^M2UAConstants mgmtError
]
dispatchOnAsp: anAsp [
<category: 'm2ua-asp-dispatch'>
anAsp handleError: self
]
]
M2UAASPTMMessage subclass: M2UAApplicationServerProcessActiveAck [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
M2UAApplicationServerProcessActiveAck class >> messageTag [
^M2UAConstants asptmActivAck
]
dispatchOnAsp: anAsp [
<category: 'm2ua-asp-dispatch'>
anAsp handleAspActiveAck: self
]
]
M2UAASPSMMessage subclass: M2UAApplicationServerProcessUpAck [
<category: 'OsmoNetwork-M2UA'>
<comment: nil>
M2UAApplicationServerProcessUpAck class >> messageTag [
^M2UAConstants aspsmUpAck
]
dispatchOnAsp: anAsp [
<category: 'm2ua-asp-dispatch'>
anAsp handleAspUpAck: self
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
STInST.RBProgramNodeVisitor subclass: M2UAStateMachineVisitor [
| states |
<comment: 'I can read the compiled methods of a M2UA state machine and generate graphviz code about the state machine and transitions that occur in it. They can be rendered by invoking the dot program on the string.'>
<category: 'OsmoNetwork-M2UA-States'>
acceptMessageNode: aNode [
aNode selector = #moveToState:
ifTrue: [self addTransition: aNode arguments first name asString].
super acceptMessageNode: aNode
]
addTransition: aStateName [
<category: 'states'>
self stateSet add: aStateName
]
stateSet [
<category: 'states'>
^states ifNil: [states := Set new]
]
]
Object subclass: M2UAStateBase [
| machine |
<category: 'OsmoNetwork-M2UA-States'>
<comment: 'I am the base class of all M2UA state machines. My direct subclasses are state machines and their subclasses are the individual states that make up the statemachine.'>
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 [
<category: 'transition'>
machine moveToState: aNewState
]
]
M2UAStateBase subclass: M2UAAsState [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
]
M2UAAsState subclass: M2UAAsStateInactive [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
onAllAspDown: anEvent [
"All ASP trans to ASP-DOWN"
<category: 'state-changes'>
self moveToState: M2UAAsStateDown
]
onAspActive: anEvent [
"one ASP trans to ACTIVE"
<category: 'state-changes'>
self moveToState: M2UAAsStateActive
]
]
M2UAAsState subclass: M2UAAsStatePending [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
onAspUp: anEvent [
"One ASP trans to ASP-ACTIVE"
<category: 'state-change'>
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"
<category: 'state-change'>
self hasInactiveAsp
ifTrue: [self moveToState: M2UAAsStateInactive]
ifFalse: [self moveToState: M2UAAsStateDown]
]
]
M2UAStateBase subclass: M2UAAspState [
<category: 'OsmoNetwork-M2UA-States'>
<comment: 'I am the base class of the ASP State Machine from RFC 3331 on Page 61.'>
M2UAAspState class >> nextPossibleStates [
^self subclassResponsibility
]
]
M2UAAspState subclass: M2UAAspStateActive [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
M2UAAspStateActive class >> nextPossibleStates [
^ {M2UAAspStateInactive. M2UAAspStateDown}
]
onAspDown: anEvent [
<category: 'state-changes'>
self moveToState: M2UAAspStateDown
]
onAspInactive: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateInactive
]
onOtherAspInAsOverrides: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateInactive
]
onSctpCdi: anEvent [
<category: 'state-changes'>
self moveToState: M2UAAspStateDown
]
onSctpRi: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateDown
]
]
M2UAAspState subclass: M2UAAspStateDown [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
M2UAAspStateDown class >> nextPossibleStates [
^{M2UAAspStateInactive}
]
onAspUp: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateInactive
]
]
M2UAAspState subclass: M2UAAspStateInactive [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
M2UAAspStateInactive class >> nextPossibleStates [
^ {M2UAAspStateActive. M2UAAspStateDown}
]
onAspActive: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateActive
]
onAspDown: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateDown
]
onSctpCdi: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateDown
]
onSctpRi: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateDown
]
]
M2UAAsState subclass: M2UAAsStateDown [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
onAspInactive: anEvent [
"One ASP trans to ASP-INACTIVE"
<category: 'state-changes'>
self movesToState: M2UAAsStateInactive
]
]
M2UAAsState subclass: M2UAAsStateActive [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
onLastActiveAspDown: anEvent [
"Last ACTIVEASP trans to ASP-INACTIVE or ASP-Down"
<category: 'state-changes'>
self startTr.
self moveToState: M2UAAsStatePending
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: M2UATag [
| tag_nr data |
<category: 'OsmoNetwork-M2UA'>
<comment: 'I represent a tag of a M2UA packet. I hold the
number of the tag and the data associated with it.'>
M2UATag class >> fromStream: aStream [
<category: 'parsing'>
^ self new
parseFrom: aStream
]
M2UATag class >> initWith: aTag data: aData [
<category: 'creation'>
^ self new
instVarNamed: #tag_nr put: aTag;
instVarNamed: #data put: aData;
yourself
]
parseFrom: aStream [
| len padding |
<category: 'parsing'>
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 [
<category: 'accessing'>
^ tag_nr
]
data [
<category: 'accessing'>
^ data ifNil: [data := ByteArray new]
]
writeOn: aMsg [
| rest |
<category: 'private'>
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 [
<category: 'accessing'>
^ self nr = aNr
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: M2UATerminology [
<category: 'OsmoNetwork-M2UA'>
<comment: 'I attempt to help with the terminology for M2UA.
M2UA is defined in IETF RFC 3331 and is actually from a family
of closely related RFCs for M3UA, SUA, M2PA.
The whole idea is that one can adapt the M2UA layer from the classlic
E1/T1 timeslots to the more modern SCTP (SIGTRAN). MTP3 and above will
not notice the difference.
The communication for M2UA is between two systems, both should be
configurable as either a client or server (listening for incoming SCTP
connections).
In general the communication is between a Signalling Gateway
(SG) and a Media Gateway Controller (MGC). In our world the MGC
would is the MSC/HLR/VLR/AuC.
What makes things complicated is the cardinality of systems. There is
an Application Server (AS), this can have multiple Application Server
Processes (ASP) for one or multiple MTP links. While the RFC onlys
says that the SG should the list of ASs in practice both ends need to
do it.'>
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: M2UAASMock [
| socket |
<category: 'OsmoNetwork-M2UA-Tests'>
<comment: 'A simple mock'>
socketService: aSocket [
<category: 'creation'>
socket := aSocket
]
handleAspActive: aMsg [
<category: 'dispatch'>
| ret |
ret := M2UAMSG new
msgClass: M2UAConstants clsASPTM;
msgType: M2UAConstants asptmActivAck;
yourself.
socket sendToAsp: ret toMessage asByteArray
]
handleAspDown: aMsg [
<category: 'dispatch'>
| ret |
ret := M2UAMSG new
msgClass: M2UAConstants clsASPSM;
msgType: M2UAConstants aspsmDownAck;
yourself.
socket sendToAsp: ret toMessage asByteArray
]
handleAspInactive: aMsg [
<category: 'dispatch'>
| ret |
ret := M2UAMSG new
msgClass: M2UAConstants clsASPTM;
msgType: M2UAConstants asptmInactivAck;
yourself.
socket sendToAsp: ret toMessage asByteArray
]
handleAspUp: aMsg [
<category: 'dispatch'>
| 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 |
<category: 'OsmoNetwork-M2UA-Tests'>
<comment: 'I mock SCTPand directly connect an AS with an ASP.'>
onSctpConnect: aBlock [
<category: 'notification'>
on_connect := aBlock
]
applicationServer: anAs [
<category: 'creation'>
as := anAs
]
applicationServerProcess: anAsp [
<category: 'creation'>
asp := anAsp
]
onSctpData: aBlock [
<category: 'creation'>
on_data := aBlock
]
onSctpReleased: aBlock [
<category: 'creation'>
on_released := aBlock
]
hostname [
<category: 'management'>
^'localhost'
]
port [
<category: 'management'>
^0
]
start [
"Nothing"
<category: 'management'>
on_connect value
]
stop [
<category: 'management'>
on_released value
]
nextPut: aMsg [
as onData: aMsg
]
sendToAsp: aMsg [
on_data
value: nil
value: nil
value: 2
value: aMsg
]
]
TestCase subclass: M2UAApplicationServerProcessTest [
<comment: 'A M2UAApplicationServerProcessTest is a test class for testing the behavior of M2UAApplicationServerProcess'>
<category: 'OsmoNetwork-M2UA-Tests'>
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 [
<comment: 'A M2UAAspStateMachineTest is a test class for testing the behavior of M2UAAspStateMachine'>
<category: 'OsmoNetwork-M2UA-Tests'>
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
]
]

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,101 @@
TestCase subclass: MTP3LabelTest [
<comment: nil>
<category: 'OsmoNetwork-MTP3-Tests'>
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 [
<comment: 'A MTP3SLTAMSGTest is a test class for testing the behavior of MTP3SLTAMSG'>
<category: 'OsmoNetwork-MTP3-Tests'>
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 [
<comment: 'A MTP3SLTMMSGTest is a test class for testing the behavior of MTP3SLTMMSG'>
<category: 'OsmoNetwork-MTP3-Tests'>
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 [
<comment: 'A MTP3ServiceIndicatorsTest is a test class for testing the behavior of MTP3ServiceIndicators'>
<category: 'OsmoNetwork-MTP3-Tests'>
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 [
<comment: 'A MTP3HeadingTest is a test class for testing the behavior of MTP3Heading'>
<category: 'OsmoNetwork-MTP3-Tests'>
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
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
LogArea subclass: LogAreaOsmo [
<comment: nil>
<category: 'OsmoNetwork-Socket'>
LogAreaOsmo class >> areaDescription [
^'Osmo socket/connection releated code'
]
LogAreaOsmo class >> areaName [
^#osmo
]
LogAreaOsmo class >> default [
^(self new)
enabled: true;
minLevel: LogLevel debug;
yourself
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
OsmoStreamSocketBase subclass: OsmoAppConnection [
| writeQueue demuxer muxer dispatcher token connect_block |
<category: 'OsmoNetwork-Socket'>
<comment: 'I connect to a OpenBSC App on the Control Port and wait for
TRAPS coming from the server and will act on these.
TODO: re-use the IPADispatcher across connections.'>
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 [
<category: 'creation'>
"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 [
<category: 'socket'>
^ Sockets.Socket remote: aHostname port: aPort.
]
connect [
<category: 'connect'>
super connect.
writeQueue := SharedQueue new.
demuxer := IPADemuxer initOn: socket.
muxer := IPAMuxer initOn: writeQueue.
self initializeDispatcher.
]
sendOne [
| msg |
<category: 'dispatch'>
msg := writeQueue next.
socket nextPutAllFlush: msg.
]
dispatchOne [
| msg |
<category: 'dispatch'>
msg := demuxer next.
dispatcher dispatch: msg first with: msg second.
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
OsmoAppConnection subclass: OsmoCtrlConnection [
| ctrlBlock |
<category: 'OsmoNetwork-Socket'>
onCtrlData: aBlock [
<category: 'ctrl-dispatch'>
ctrlBlock := aBlock
]
handleCTRL: aCtrl [
<category: 'ctrl-dispatch'>
ctrlBlock value: aCtrl.
]
initializeDispatcher [
super initializeDispatcher.
dispatcher
addHandler: IPAConstants protocolOsmoCTRL
on: self with: #handleCTRL:.
]
sendCtrlData: aData [
self nextPut: aData with: IPAConstants protocolOsmoCTRL
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
PP.PPCompositeParser subclass: CtrlGrammar [
<category: 'OsmoNetwork-Control'>
<comment: 'I can parse the control interface'>
start [
<category: 'grammar'>
^ self message
]
message [
<category: 'message'>
^ self trapMessage / self notSupported
]
notSupported [
<category: 'not-supported'>
^ #any asParser plus.
]
trapMessage [
<category: 'trap'>
^ 'TRAP' asParser trim,
self identifier trim,
self variable trim,
#any asParser plus flatten
]
identifier [
<category: 'identifier'>
^ #digit asParser plus flatten
]
variable [
<category: 'variable'>
^ self variablePart plus
]
variablePart [
<category: 'variable'>
^ (#digit asParser plus / #letter asParser / $- asParser / $_ asParser) plus flatten,
$. asParser optional
]
]
Object subclass: CtrlCmd [
| msg |
<category: 'OsmoNetwork-Control'>
<comment: 'I am a base class without any functions'>
CtrlCmd class >> with: aMsg [
<category: 'creation'>
^ self new
instVarNamed: #msg put: aMsg;
yourself
]
isTrap [
<category: 'accessing'>
^ false
]
msg [
<category: 'accesing'>
^ msg
]
]
CtrlCmd subclass: CtrlTrap [
<category: 'OsmoNetwork-Control'>
<comment: 'I am a trap'>
CtrlTrap class >> isFor: aPath [
<category: 'creation'>
^ self subclassResponsibility
]
CtrlTrap class >> isFor: aPath value: aValue [
^self isFor: aPath
]
CtrlTrap class >> findTrapFor: nodes [
<category: 'creation'>
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 |
<category: 'OsmoNetwork-Control'>
<comment: 'I handle location traps'>
CtrlLocationTrap class >> isFor: aPath [
<category: 'creation'>
^ 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 [
<category: 'private'>
net_nr := aStr asNumber
]
bsc: aStr [
<category: 'private'>
bsc_nr := aStr asNumber
]
bts: aBts [
<category: 'private'>
bts_nr := aBts asNumber
]
location: aLoc [
<category: 'private'>
location := aLoc substrings: ','.
location size = 8 ifFalse: [
^ self error: 'Failed to parse location'.
].
]
net [
<category: 'accessing'>
^ net_nr
]
bsc [
<category: 'accessing'>
^ bsc_nr
]
bts [
^ bts_nr
]
locTimeStamp [
<category: 'accessing'>
^ location at: 1
]
locState [
<category: 'accessing'>
^ location at: 2
]
locLat [
<category: 'accessing'>
^ location at: 3
]
locLon [
<category: 'accessing'>
^ location at: 4
]
locHeight [
<category: 'accessing'>
^ location at: 5
]
trxAvailable [
<category: 'accessing'>
^ (location at: 6) = 'operational'
]
trxAdminLock [
<category: 'accessing'>
^ (location at: 7) = 'locked'
]
rfPolicy [
<category: 'accessing'>
^ location at: 8
]
rfPolicyOn [
<category: 'accessing'>
^ self rfPolicy = 'on'
]
rfPolicyOff [
<category: 'accessing'>
^ self rfPolicy = 'off'
]
rfPolicyGrace [
<category: 'accessing'>
^ self rfPolicy = 'grace'
]
rfPolicyUnknown [
<category: 'accessing'>
^ self rfPolicy = 'unknown'
]
]
CtrlTrap subclass: CtrlCallStatTrap [
| dict |
<category: 'OsmoNetwork-Control'>
<comment: 'I can parse the callstats generated by the NAT'>
CtrlCallStatTrap class >> isFor: aPath [
<category: 'creation'>
(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 [
<category: 'creation'>
^ (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 [
<category: 'OsmoNetwork-Control'>
<comment: 'I parse the tokens from the Ctrl grammar'>
trapMessage [
^ super trapMessage => [:nodes |
CtrlTrap findTrapFor: nodes].
]
notSupported [
^ super notSupported => [:nodes | CtrlCmd with: (String withAll: nodes)]
]
]

View File

@ -0,0 +1,104 @@
"All rights reserved"
PP.PPCompositeParserTest subclass: CtrlGrammarTest [
<category: 'OsmoNetwork-Control-Tests'>
<comment: 'I test some parts of the grammar'>
CtrlGrammarTest class >> packageNamesUnderTest [
<category: 'accessing'>
^ #('CtrlGrammar')
]
parserClass [
<category: 'accessing'>
^ CtrlGrammar
]
testLocationStateTrap [
| data res |
<category: 'accessing'>
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 [
<category: 'OsmoNetwork-Control-Tests'>
<comment: 'I test some parts of the grammar'>
CtrlParserTest class >> packageNamesUnderTest [
<category: 'accessing'>
^ #('CtrlParser')
]
parserClass [
<category: 'accessing'>
^ CtrlParser
]
testLocationStateTrap [
| data res |
<category: 'accessing'>
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 |
<category: 'accessing'>
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'.
]
]

View File

@ -0,0 +1,13 @@
"I represent the logging areas"
Osmo.LogArea subclass: LogAreaCTRL [
<category: 'OsmoNetwork-Control'>
LogAreaCTRL class >> areaName [ ^ #ctrl ]
LogAreaCTRL class >> areaDescription [ ^ 'Osmo CTRL handling' ]
LogAreaCTRL class >> default [
^ self new
enabled: true;
minLevel: Osmo.LogLevel debug;
yourself
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: OsmoStreamSocketBase [
| socket hostname port tx_proc rx_proc started |
<category: 'OsmoNetwork-Socket'>
<comment: 'I am the base class for streaming related sockets. I help with
supervising the RX/TX process and re-starting.'>
OsmoStreamSocketBase class >> connectionException [
<category: 'pharo-porting'>
^ SystemExceptions.FileError
]
hostname: aHostname [
<category: 'creation'>
hostname := aHostname
]
port: aPort [
<category: 'creation'>
port := aPort
]
hostname [
<category: 'accessing'>
^hostname
]
port [
<category: 'accessing'>
^port
]
targetDescription [
<category: 'accessing'>
^(WriteStream on: String new)
nextPutAll: hostname;
nextPut: $:;
nextPutAll: port asString;
contents
]
connect [
<category: 'connect'>
socket ifNotNil: [socket close].
socket := self createConnection: hostname port: port
]
start [
<category: 'connect'>
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 [
<category: 'connect'>
started := false.
self terminate
"A reconnect timer might be running right now"
]
terminate [
<category: 'connect'>
tx_proc ifNotNil: [tx_proc terminate].
rx_proc ifNotNil: [rx_proc terminate].
socket ifNotNil:
[[socket close.] ensure: [ socket := nil ]].
]
driveDispatch [
<category: 'private'>
[
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 [
<category: 'private'>
[
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 [
<category: 'private'>
self logNotice: ('Going to reconnect socket to ', self targetDescription) area: #osmo.
self terminate.
started ifTrue: [self start]
]
scheduleReconnect [
<category: 'private'>
socket ifNotNil: [socket close. socket := nil].
TimerScheduler instance scheduleInSeconds: 1 block: [self reconnect].
"We are done now"
Processor activeProcess terminate
]
createConnection: aHostname port: aPort [
<category: 'internal'>
self subclassResponsibility
]
dispatchOne [
<category: 'internal'>
self subclassResponsibility
]
sendOne [
<category: 'internal'>
self subclassResponsibility
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: OsmoUDPSocket [
| socket queue rx tx net_exit name on_data |
<category: 'OsmoNetwork-Socket'>
<comment: 'I help in sending and dispatching UDP messages. I will
start two processes for socket handling.'>
OsmoUDPSocket class >> new [
<category: 'creation'>
^ super new
initialize;
yourself
]
initialize [
<category: 'creation'>
queue := SharedQueue new.
net_exit := Semaphore new.
]
name: aName [
<category: 'creation'>
name := aName
]
onData: aBlock [
<category: 'creation'>
on_data := aBlock
]
start: aSocket [
<category: 'creation'>
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 [
<category: 'processing'>
[ | data |
socket ensureReadable.
socket isOpen ifFalse: [
^self logNotice: name, ' socket closed.' area: #core].
data := socket next.
on_data value: data.
] repeat.
]
runTXProcess [
<category: 'processing'>
[ | data |
data := queue next.
data = nil ifTrue: [
^self logNotice: name, ' TX asked to quit.' area: #core].
socket nextPut: data.
] repeat.
]
stop [
<category: 'processing'>
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 [
<category: 'sending'>
queue nextPut: aData
]
]

View File

@ -0,0 +1,87 @@
<package>
<name>OsmoNetwork</name>
<namespace>Osmo</namespace>
<prereq>OsmoLogging</prereq>
<prereq>OsmoCore</prereq>
<prereq>PetitParser</prereq>
<prereq>Sockets</prereq>
<prereq>Parser</prereq>
<filein>core/Extensions.st</filein>
<filein>core/ExtensionsGST.st</filein>
<filein>core/MessageStructure.st</filein>
<filein>core/MessageBuffer.st</filein>
<filein>core/LogAreas.st</filein>
<filein>core/TLV.st</filein>
<filein>isup/ISUP.st</filein>
<filein>isup/isup_generated.st</filein>
<filein>isup/ISUPExtensions.st</filein>
<filein>ipa/IPAConstants.st</filein>
<filein>ipa/IPAConstantsGST.st</filein>
<filein>ipa/IPADispatcher.st</filein>
<filein>ipa/IPAMuxer.st</filein>
<filein>ipa/IPAProtoHandler.st</filein>
<filein>ipa/IPAMsg.st</filein>
<filein>sccp/SCCP.st</filein>
<filein>sccp/SCCPAddress.st</filein>
<filein>sccp/SCCPGlobalTitle.st</filein>
<filein>sccp/SCCPGlobalTitleTranslation.st</filein>
<filein>mtp3/MTP3Messages.st</filein>
<filein>ua/XUA.st</filein>
<filein>m2ua/M2UAConstants.st</filein>
<filein>m2ua/M2UAStates.st</filein>
<filein>m2ua/M2UATag.st</filein>
<filein>m2ua/M2UAMSG.st</filein>
<filein>m2ua/M2UAMessages.st</filein>
<filein>m2ua/M2UAStates.st</filein>
<filein>m2ua/M2UAAspStateMachine.st</filein>
<filein>m2ua/M2UAApplicationServerProcess.st</filein>
<filein>m2ua/M2UALayerManagement.st</filein>
<filein>m2ua/M2UATerminology.st</filein>
<filein>m2ua/M2UAExamples.st</filein>
<filein>osmo/LogAreaOsmo.st</filein>
<filein>osmo/OsmoUDPSocket.st</filein>
<filein>osmo/OsmoCtrlLogging.st</filein>
<filein>osmo/OsmoCtrlGrammar.st</filein>
<filein>osmo/OsmoStreamSocketBase.st</filein>
<filein>osmo/OsmoAppConnection.st</filein>
<filein>osmo/OsmoCtrlConnection.st</filein>
<test>
<prereq>PetitParserTests</prereq>
<sunit>Osmo.SCCPTests</sunit>
<sunit>Osmo.IPATests</sunit>
<sunit>Osmo.IPAGSTTests</sunit>
<sunit>Osmo.IPAMsgTests</sunit>
<sunit>Osmo.MessageBufferTest</sunit>
<sunit>Osmo.ISUPGeneratedTest</sunit>
<sunit>Osmo.OsmoUDPSocketTest</sunit>
<sunit>Osmo.TLVDescriptionTest</sunit>
<sunit>Osmo.CtrlGrammarTest</sunit>
<sunit>Osmo.CtrlParserTest</sunit>
<sunit>Osmo.M2UAMSGTests</sunit>
<sunit>Osmo.M2UAApplicationServerProcessTest</sunit>
<sunit>Osmo.M2UAAspStateMachineTest</sunit>
<sunit>Osmo.MTP3LabelTest</sunit>
<sunit>Osmo.MTP3SLTAMSGTest</sunit>
<sunit>Osmo.MTP3SLTMMSGTest</sunit>
<sunit>Osmo.MTP3ServiceIndicatorsTest</sunit>
<sunit>Osmo.MTP3HeadingTest</sunit>
<filein>Tests.st</filein>
<filein>core/TLVTests.st</filein>
<filein>isup/ISUPTests.st</filein>
<filein>ipa/IPATests.st</filein>
<filein>osmo/OsmoCtrlGrammarTest.st</filein>
<filein>m2ua/M2UATests.st</filein>
<filein>mtp3/MTP3MessagesTests.st</filein>
</test>
</package>

View File

@ -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 [
<category: 'pharo-porting'>
^(SocketStream openConnectionToHostNamed: aHostname port: aPort)
binary;
noTimeout;
yourself
]
]
OsmoStreamSocketBase extend [
driveDispatch [
<category: 'private'>
[
[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 [
<category: 'private'>
[
self sendOne.
] on: ConnectionClosed do: [:e |
e logException: 'OsmoAppConnection send failed' area: #osmo.
self scheduleReconnect.
]
]
]
OsmoStreamSocketBase class extend [
connectionException [
<category: 'pharo-porting'>
^ConnectionTimedOut
]
]

View File

@ -0,0 +1,60 @@
ByteArray extend [
shortAt: index [
<category: '*OsmoNetwork-Pharo'>
"This is not signed right now"
^ self ushortAt: index
]
ushortAt: index [
<category: '*OsmoNetwork-Pharo'>
^ ((self at: index + 1) bitShift: 8) bitOr: (self at: index)
]
uintAt: index [
<category: '*OsmoNetwork-Pharo'>
| 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 [
<category: '*OsmoNetwork-Pharo'>
^ self new
object: anObject;
messageText: aMessage;
signal
]
]
Socket extend [
ensureReadable [
<category: '*OsmoNetwork-Pharo'>
^ self isValid
]
isOpen [
<category: '*OsmoNetwork-Pharo'>
^ self isConnected
]
next [
| data |
<category: '*OsmoNetwork-Pharo'>
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
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: SCCPHelper [
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the SCCP message class constants and provide
an easy way to create specific messages.'>
SCCPHelper class >> msgCr [ <category: 'constants'> ^ 16r01 ]
SCCPHelper class >> msgCc [ <category: 'constants'> ^ 16r02 ]
SCCPHelper class >> msgCref [ <category: 'constants'> ^ 16r03 ]
SCCPHelper class >> msgRlsd [ <category: 'constants'> ^ 16r04 ]
SCCPHelper class >> msgRlc [ <category: 'constants'> ^ 16r05 ]
SCCPHelper class >> msgDt1 [ <category: 'constants'> ^ 16r06 ]
SCCPHelper class >> msgDt2 [ <category: 'constants'> ^ 16r07 ]
SCCPHelper class >> msgAk [ <category: 'constants'> ^ 16r08 ]
SCCPHelper class >> msgUdt [ <category: 'constants'> ^ 16r09 ]
SCCPHelper class >> msgUdts [ <category: 'constants'> ^ 16r0A ]
SCCPHelper class >> msgEd [ <category: 'constants'> ^ 16r0B ]
SCCPHelper class >> msgEa [ <category: 'constants'> ^ 16r0C ]
SCCPHelper class >> msgRsr [ <category: 'constants'> ^ 16r0D ]
SCCPHelper class >> msgRsc [ <category: 'constants'> ^ 16r0E ]
SCCPHelper class >> msgErr [ <category: 'constants'> ^ 16r0F ]
SCCPHelper class >> msgIt [ <category: 'constants'> ^ 16r10 ]
SCCPHelper class >> msgXudt [ <category: 'constants'> ^ 16r11 ]
SCCPHelper class >> msgXudts[ <category: 'constants'> ^ 16r12 ]
SCCPHelper class >> msgLudt [ <category: 'constants'> ^ 16r13 ]
SCCPHelper class >> msgLudts[ <category: 'constants'> ^ 16r14 ]
SCCPHelper class >> pncData [ <category: 'constants'> ^ 16r0F ]
SCCPHelper class >> pncEoO [ <category: 'constants'> ^ 16r00 ]
SCCPHelper class >> createCR: src dest: dest data: aData [
<category: 'creation'>
^ (SCCPConnectionRequest initWith: src dest: dest data: aData)
toMessage.
]
SCCPHelper class >> createRLSD: src dest: dest cause: cause [
<category: 'creation'>
^ (SCCPConnectionReleased initWithDst: dest src: src cause: cause)
toMessage.
]
SCCPHelper class >> createDT1: dst data: data [
<category: 'creation'>
^ (SCCPConnectionData initWith: dst data: data)
toMessage.
]
]
Object subclass: SCCPPNC [
| dict |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I can parse and write the optional
data of SCCP messages.'>
SCCPPNC class >> parseFrom: aPnc [
| dict pnc |
<category: 'parsing'>
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 [
<category: 'accessing'>
self dict at: aKey put: aValue.
]
at: aKey [
<category: 'accessing'>
^ self dict at: aKey.
]
dict [
<category: 'accessing'>
^ dict ifNil: [dict := Dictionary new.]
]
dict: aDict [
<category: 'private'>
dict := aDict.
]
writeOn: aMsg [
<category: 'encoding'>
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 [
<category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the Address Reference, e.g. the source
or destination reference address as used for SCCP connections.'>
SCCPAddrReference class >> store: anAddress on: aMsg [
"Store the threee bytes of an sccp address on a messagebuffer"
<category: 'encoding'>
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"
<category: 'encoding'>
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"
<category: 'encoding'>
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 [
<category: 'OsmoNetwork-SCCP'>
<comment: 'I am the generic base class for all defined
SCCP messages. You should only deal with me to decode
data.'>
SCCPMessage class >> decode: aByteArray [
| type |
<category: 'parsing'>
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 |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of a connection request.'>
SCCPConnectionRequest class >> msgType [
<category: 'factory'>
^ SCCPHelper msgCr
]
SCCPConnectionRequest class >> initWith: src dest: dest pnc: pnc [
<category: 'construction'>
^ self new
src: src dest: dest pnc: pnc;
yourself
]
SCCPConnectionRequest class >> initWith: src dest: dest data: data [
<category: 'construction'>
| 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 |
<category: 'parsing'>
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 [
<category: 'accessing'>
^ src
]
dest [
<category: 'accessing'>
^ dst
]
data [
<category: 'accessing'>
^ pnc at: SCCPHelper pncData.
]
data: aData [
<category: 'accessing'>
pnc at: SCCPHelper pncData put: aData.
]
src: aSrc dest: aDest pnc: aPnc [
<category: 'accessing'>
src := aSrc.
dst := aDest.
pnc := aPnc.
]
writeOn: aMsg [
<category: 'encoding'>
| 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 |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of a connection confirm.'>
SCCPConnectionConfirm class >> msgType [
<category: 'factory'>
^ SCCPHelper msgCc
]
SCCPConnectionConfirm class >> initWithSrc: aSrc dst: aDst [
<category: 'creation'>
^ self new
src: aSrc dst: aDst;
yourself
]
SCCPConnectionConfirm class >> parseFrom: aMsg [
| src dst proto optional |
<category: 'parsing'>
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 [
<category: 'encoding'>
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 [
<category: 'accessing'>
src := aSrc.
dst := aDst.
]
src [
<category: 'accessing'>
^ src
]
dst [
<category: 'accessing'>
^ dst
]
pnc [
<category: 'accessing'>
^ pnc ifNil: [ pnc := SCCPPNC new. ]
]
]
SCCPMessage subclass: SCCPConnectionData [
| dst data |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of a data memssage.'>
SCCPConnectionData class >> msgType [
<category: 'factory'>
^ SCCPHelper msgDt1
]
SCCPConnectionData class >> initWith: dst data: data [
<category: 'creation'>
^ (self new)
dst: dst;
data: data;
yourself.
]
SCCPConnectionData class >> parseFrom: aByteArray [
| more_data var_start addr size data |
<category: 'parsing'>
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 [
<category: 'private'>
dst := aDst.
]
data: aData [
<category: 'private'>
data := aData.
data size > 16rFF ifTrue: [
self error: ('Data must be < 256 in size but was <1p>' expandMacrosWith: data size)
].
]
dst [
<category: 'accessing'>
^ dst
]
data [
<category: 'accessing'>
^ data
]
writeOn: aMsg [
| dat |
<category: 'encoding'>
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 |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of a connection release message.'>
SCCPConnectionReleased class >> msgType [
<category: 'factory'>
^ SCCPHelper msgRlsd
]
SCCPConnectionReleased class >> initWithDst: aDst src: aSrc cause: aCause [
<category: 'creation'>
^ self new
dst: aDst;
src: aSrc;
cause: aCause;
yourself.
]
SCCPConnectionReleased class >> parseFrom: aByteArray [
| dst src cause |
<category: 'parsing'>
dst := SCCPAddrReference fromByteArray: (aByteArray copyFrom: 2).
src := SCCPAddrReference fromByteArray: (aByteArray copyFrom: 5).
cause := aByteArray at: 8.
^ SCCPConnectionReleased initWithDst: dst src: src cause: cause.
]
dst [
<category: 'accessing'>
^ dst
]
src [
<category: 'accessing'>
^ src
]
cause [
<category: 'accessing'>
^ cause
]
dst: aDst [
<category: 'accessing'>
dst := aDst
]
src: aSrc [
<category: 'accessing'>
src := aSrc
]
cause: aCause [
<category: 'accessing'>
cause := aCause
]
pnc [
<category: 'accessing'>
^ pnc ifNil: [pnc := SCCPPNC new]
]
writeOn: aMsg [
<category: 'encoding'>
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 |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of a released connection.'>
SCCPConnectionReleaseComplete class >> msgType [
<category: 'fields'>
^ SCCPHelper msgRlc.
]
SCCPConnectionReleaseComplete class >> initWithDst: aDst src: aSrc [
<category: 'creation'>
^ self new
dst: aDst; src: aSrc;
yourself
]
SCCPConnectionReleaseComplete class >> parseFrom: aByteArray [
<category: 'parsing'>
^ self new
dst: (SCCPAddrReference fromByteArray: (aByteArray copyFrom: 2 to: 4));
src: (SCCPAddrReference fromByteArray: (aByteArray copyFrom: 5 to: 7));
yourself
]
dst [
<category: 'accessing'>
^ dst
]
dst: aDst [
<category: 'accessing'>
dst := aDst.
]
src [
<category: 'accessing'>
^ src
]
src: aSrc [
<category: 'accessing'>
src := aSrc.
]
writeOn: aMsg [
<category: 'encoding'>
aMsg putByte: self class msgType.
SCCPAddrReference store: dst on: aMsg.
SCCPAddrReference store: src on: aMsg.
]
]
SCCPMessage subclass: SCCPUDT [
| called calling data error udtClass |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of a connection less data message.'>
SCCPUDT class >> msgType [
<category: 'fields'>
^ SCCPHelper msgUdt
]
SCCPUDT class >> initWith: aCalled calling: aCalling data: aData [
<category: 'creation'>
^ self new
calledAddr: aCalled;
callingAddr: aCalling;
data: aData;
yourself
]
SCCPUDT class >> parseFrom: aByteArray [
| called calledData calling callingData data dataData dataSize |
<category: 'parsing'>
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 [
<category: 'accessing'>
called := aCalled
]
calledAddr [
<category: 'accessing'>
^ called
]
callingAddr: aCalling [
<category: 'accessing'>
calling := aCalling
]
callingAddr [
<category: 'accessing'>
^ calling
]
data [
<category: 'accessing'>
^ data
]
data: aData [
<category: 'accessing'>
data := aData.
]
errorHandling: aStrategy [
<category: 'accessing'>
error := aStrategy.
]
errorHandling [
<category: 'accessing'>
^ error ifNil: [0]
]
udtClass: aClass [
<category: 'accessing'>
udtClass := aClass.
]
udtClass [
<category: 'accessing'>
^ udtClass ifNil: [0]
]
writeOn: aMsg [
| calledData callingData dat |
<category: 'encoding'>
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 |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I hold the data of an inactivity test.'>
SCCPInactivityTest class >> msgType [
<category: 'field'>
^ SCCPHelper msgIt
]
SCCPInactivityTest class >> initWithDst: aDst src: aSrc [
<category: 'creation'>
^ self new
dst: aDst;
src: aSrc;
yourself.
]
SCCPInactivityTest class >> parseFrom: aByteArray [
| dst src proto seq credit |
<category: 'parsing'>
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 [
<category: 'stuff'>
src := aSrc.
]
src [
<category: 'stuff'>
^ src
]
dst: aDst [
<category: 'stuff'>
dst := aDst
]
dst [
<category: 'stuff'>
^ dst
]
credit [
<category: 'stuff'>
^ credit ifNil: [0]
]
credit: aCredit [
<category: 'stuff'>
credit := aCredit
]
protoClass [
<category: 'stuff'>
^ proto ifNil: [0]
]
protoClass: aClass [
<category: 'stuff'>
proto := aClass.
]
seq [
<category: 'stuff'>
^ seq ifNil: [ByteArray new: 2]
]
seq: aSeq [
<category: 'stuff'>
seq := aSeq.
]
writeOn: aMsg [
<category: 'encoding'>
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.
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: SCCPAddress [
| subSystemNumber globalTitle routedOnSsn pointCode gti_ind |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the SCCP Address including the
SSN, GTI if present.'>
SCCPAddress class >> ssnNotKnown [ <category: 'constants'> ^ 0 ]
SCCPAddress class >> ssnSCCPMgnt [ <category: 'constants'> ^ 1 ]
SCCPAddress class >> ssnITURsrvd [ <category: 'constants'> ^ 2 ]
SCCPAddress class >> ssnISUP [ <category: 'constants'> ^ 3 ]
SCCPAddress class >> ssnOMA [ <category: 'constants'> ^ 4 ]
SCCPAddress class >> ssnMAP [ <category: 'constants'> ^ 5 ]
SCCPAddress class >> ssnHLR [ <category: 'constants'> ^ 6 ]
SCCPAddress class >> ssnVLR [ <category: 'constants'> ^ 7 ]
SCCPAddress class >> ssnMSC [ <category: 'constants'> ^ 8 ]
SCCPAddress class >> ssnEIC [ <category: 'constants'> ^ 9 ]
SCCPAddress class >> ssnAUC [ <category: 'constants'> ^ 10 ]
SCCPAddress class >> ssnISUPSRV [ <category: 'constants'> ^ 11 ]
SCCPAddress class >> ssnReserved [ <category: 'constants'> ^ 12 ]
SCCPAddress class >> ssnBroadISDN[ <category: 'constants'> ^ 13 ]
SCCPAddress class >> ssnTCTest [ <category: 'constants'> ^ 14 ]
SCCPAddress class >> ssnSGSN [ <category: 'constants'> ^149 ]
SCCPAddress class >> createWith: ssn [
<category: 'creation'>
^self createWith: ssn pointCode: nil
]
SCCPAddress class >> createWith: ssn poi: aPointCode [
<category: 'creation'>
self deprecated: 'Use >>#createWith:pointCode: instead'.
^self createWith: ssn pointCode: aPointCode
]
SCCPAddress class >> createWith: ssn pointCode: aPointCode [
<category: 'creation'>
^(self new)
ssn: ssn;
routedOnSSN: true;
pointCode: aPointCode;
yourself
]
SCCPAddress class >> createForSSN: aSymbol [
<category: 'creation'>
^ self createWith: (self perform: ('ssn', aSymbol asUppercase) asSymbol)
]
SCCPAddress class >> parseFrom: aByteArray [
| routed_ssn gti_ind gti len ai ssn pointCode dat |
<category: 'parsing'>
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 [
<category: 'deprecated'>
self routedOnSubSystenNumber: aFlag
]
routedOnSubSystenNumber: aFlag [
<category: 'ssn'>
routedOnSsn := aFlag
]
routedOnSSN [
<category: 'ssn'>
^ routedOnSsn ifNil: [false]
]
gti [
<category: 'deprecated'>
^ self globalTitle
]
globalTitle [
<category: 'gti'>
^ globalTitle
]
gtiInd [
<category: 'gti'>
^ gti_ind
]
globalTitle: aGlobalTitle indicator: aGtiInd [
<category: 'gti'>
globalTitle := aGlobalTitle.
gti_ind := aGtiInd bitAnd: 16rF.
]
gti: aGlobalTitle indicator: aGtiInd [
<category: 'gti'>
self globalTitle: aGlobalTitle indicator: aGtiInd
]
gtiAsParsed [
<category: 'gti'>
^self parseGlobalTitle
]
parseGlobalTitle [
<category: 'gti'>
^ gti_ind = 0
ifTrue: [nil]
ifFalse: [SCCPGlobalTitle initWith: gti_ind data: globalTitle].
]
gtiFromAddr: aGlobalTitle [
<category: 'gti'>
gti_ind := aGlobalTitle class subType.
globalTitle := aGlobalTitle asByteArray.
]
poi: aPointCode [
<category: 'deprecated'>
self deprecated: 'Use >>#pointCode: instead'.
self pointCode: aPointCode
]
poi [
<category: 'deprecated'>
self deprecated: 'Use >>#pointCode instead'.
^self pointCode
]
pointCode [
<category: 'point-code-indicator'>
^pointCode
]
pointCode: aPointCode [
"When a non-nil point code is set the pointcode indicator will be set in the
address information."
<category: 'point-code-indicator'>
pointCode := aPointCode
]
ssn: aSubSystemNumber [
<category: 'deprecated'>
"deprecated"
self subSystemNumber: aSubSystemNumber
]
subSystemNumber: aSubSystemNumber [
subSystemNumber := aSubSystemNumber
]
ssn [
<category: 'deprecated'>
^ self subSystemNumber
]
subSystemNumber [
<category: 'accessing'>
^ subSystemNumber
]
asByteArray [
"Most simple address storing routine"
| ai data |
<category: 'encoding'>
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
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
Object subclass: SCCPGlobalTitle [
| indicator nai data |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the Global Title of Q.713.'>
SCCPGlobalTitle class >> gtiIndNoGTI [ <category: 'gti'> ^ 0 ]
SCCPGlobalTitle class >> gtiIndGTI [ <category: 'gti'> ^ 1 ]
SCCPGlobalTitle class >> gtiIndTransOnlyGTI [ <category: 'gti'> ^ 2 ]
SCCPGlobalTitle class >> gtiIndTransNumbrPlanAndEnc [ <category: 'gti'> ^ 3 ]
SCCPGlobalTitle class >> gtiIndTransNumbrAndMore [ <category: 'gti'> ^ 4 ]
SCCPGlobalTitle class >> naiUnknown [ <category: 'nai'> ^ 0 ]
SCCPGlobalTitle class >> naiSubscriber [ <category: 'nai'> ^ 1 ]
SCCPGlobalTitle class >> naiReservedNational [ <category: 'nai'> ^ 2 ]
SCCPGlobalTitle class >> naiNationalSign [ <category: 'nai'> ^ 3 ]
SCCPGlobalTitle class >> naiInternationalNumber [ <category: 'nai'> ^ 4 ]
SCCPGlobalTitle class >> npUnknown [ <category: 'numbering-plan'> ^ 0 ]
SCCPGlobalTitle class >> npISDN [ <category: 'numbering-plan'> ^ 1 ]
SCCPGlobalTitle class >> npGeneric [ <category: 'numbering-plan'> ^ 2 ]
SCCPGlobalTitle class >> npData [ <category: 'numbering-plan'> ^ 3 ]
SCCPGlobalTitle class >> npTelex [ <category: 'numbering-plan'> ^ 4 ]
SCCPGlobalTitle class >> npMaritime [ <category: 'numbering-plan'> ^ 5 ]
SCCPGlobalTitle class >> npLand [ <category: 'numbering-plan'> ^ 6 ]
SCCPGlobalTitle class >> npMobile [ <category: 'numbering-plan'> ^ 7 ]
SCCPGlobalTitle class >> esUnknown [ <category: 'encoding-scheme'> ^ 0 ]
SCCPGlobalTitle class >> esBCDOdd [ <category: 'encoding-scheme'> ^ 1 ]
SCCPGlobalTitle class >> esBCDEven [ <category: 'encoding-scheme'> ^ 2 ]
SCCPGlobalTitle class >> esNational [ <category: 'encoding-scheme'> ^ 3 ]
SCCPGlobalTitle class >> initWith: gti_ind data: gti [
<category: 'creation'>
self allSubclassesDo: [:each |
each subType = gti_ind
ifTrue: [
^ each initWith: gti.
].
].
^ self error: ('Unhandled gti indicator: <1p>' expandMacrosWith: gti_ind).
]
SCCPGlobalTitle class >> map: aDigit [
<category: 'creation'>
^ (aDigit >= 0 and: [aDigit <= 9])
ifTrue: [ (aDigit + 48) asCharacter ]
ifFalse: [ $N ]
]
SCCPGlobalTitle class >> unmap: aChar [
| digit |
<category: 'parsing'>
digit := aChar asInteger.
^ (digit >= 48 and: [digit <= 57])
ifTrue: [ digit - 48 ]
ifFalse: [ 16rF ].
]
SCCPGlobalTitle class >> parseAddr: data encoding: aEnc [
| odd split |
<category: 'parsing'>
(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 |
<category: 'creation'>
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)).
].
]
]

View File

@ -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 <http://www.gnu.org/licenses/>.
"
SCCPGlobalTitle subclass: SCCPGlobalTitleTranslation [
| trans plan nature addr |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the global title translation specific
encoing of a SCCP header.'>
SCCPGlobalTitleTranslation class >> subType [ <category: 'constants'> ^ 4 ]
SCCPGlobalTitleTranslation class >> initWith: data [
| enc |
<category: 'creation'>
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 [
<category: 'accessing'>
^ trans ifNil: [ 0 ]
]
translation: aTrans [
<category: 'accessing'>
trans := aTrans
]
plan [
<category: 'accessing'>
^ plan
]
plan: aPlan [
<category: 'accessing'>
plan := aPlan
]
encoding [
<category: 'accessing'>
^addr size odd
ifTrue: [1]
ifFalse: [2]
]
nature [
<category: 'accessing'>
^ nature
]
nature: aNai [
<category: 'accessing'>
nature := aNai
]
address [
<category: 'accessing'>
^addr
]
addr [
<category: 'accessing'>
^self address
]
addr: anAddr [
<category: 'accessing'>
addr := anAddr
]
asByteArray [
| data |
<category: 'encoding'>
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
]
]

Some files were not shown because too many files have changed in this diff Show More