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

Merge remote-tracking branch 'osmo-st-network/master'

This commit is contained in:
Holger Hans Peter Freyther 2012-10-11 23:16:09 +02:00
commit 97b9da21e2
74 changed files with 6905 additions and 1 deletions

@ -1 +0,0 @@
Subproject commit d7b2323602771681119bdb0507de3fc58f519aae

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

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

View File

@ -0,0 +1,158 @@
"
(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/>.
"
PackageLoader fileInPackage: 'Sockets'.
Integer extend [
swap16 [
| tmp |
<category: '*-OsmoCore-message'>
tmp := self bitAnd: 16rFFFF.
^ (tmp bitShift: -8) bitOr: ((tmp bitAnd: 16rFF) bitShift: 8)
]
swap32 [
| tmp |
"Certainly not the most effective way"
<category: '*-OsmoCore-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: '*-OsmoCore-message'>
msg := Osmo.MessageBuffer new.
self writeOn: msg.
^ msg
]
toMessageOrByteArray [
<category: '*-OsmoCore-message'>
^ self toMessage
]
]
ByteArray extend [
toMessageOrByteArray [
<category: '*-OsmoCore-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: '*-OsmoCore-message'>
^self nextBytes: 2 signed: false
]
nextBytes: n signed: signed [
"Private - Get an integer out of the next anInteger bytes in the stream"
<category: '*-OsmoCore-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: '*-OsmoCore-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: '*-OsmoCore-message'>
^self nextBytes: 2 signed: false
]
nextBytes: n signed: signed [
"Private - Get an integer out of the next anInteger bytes in the stream"
<category: '*-OsmoCore-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: '*-OsmoCore-message'>
| a |
a := self next.
^a isNil ifTrue: [a] ifFalse: [a asInteger]
]
]
ByteArray extend [
castTo: type [
<category: '*-OsmoCore-message'>
^ (CObject new storage: self) castTo: type
]
]
CCompound subclass: CPackedStruct [
<shape: #word>
<category: 'Language-C interface'>
<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.
]
]

View File

@ -0,0 +1,104 @@
"
(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 ]
"Extensions in Osmocom coming with the OsmoExtension header"
IPAConstants class >> osmoCtrl [ <category: 'constants'> ^ 16r00 ]
IPAConstants class >> osmoMgcp [ <category: 'constants'> ^ 16r01 ]
IPAConstants class >> osmoLac [ <category: '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}
]
]
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,57 @@
"
(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 ', aStream displayString area: #ipa.
^ false
].
handler value: aData.
]
]

193
osmo-st-network/IPAMsg.st Normal file
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 size;
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 size;
putByte: each key;
putByteArray: each value.
].
]
]

108
osmo-st-network/IPAMuxer.st Normal file
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,98 @@
"
(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'>
handlers := nil.
IPAProtoHandler class >> initialize [
<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:.
]
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 := 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.
'pong' printNl.
]
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.
]

152
osmo-st-network/IPATests.st Normal file
View File

@ -0,0 +1,152 @@
"
(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 |
IPATests class >> packageNamesUnderTest [
<category: 'accessing'>
^ #('OsmoNetwork')
]
testSize [
self assert: IPASCCPState sizeof = 25.
]
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-IPA'>
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.
]
]
]

263
osmo-st-network/ISUP.st Normal file
View File

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

View File

@ -0,0 +1,68 @@
"
(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 [
<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 structure.
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 :class |
self playWith: 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.
]
]

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

413
osmo-st-network/M2UA.st Normal file
View File

@ -0,0 +1,413 @@
"
(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: UAConstants [
"
Management (MGMT) Message [IUA/UA/M3UA/SUA]
Transfer Messages [M3UA]
SS7 Signalling Network Management (SSNM) Messages [M3UA/SUA]
ASP State Maintenance (ASPSM) Messages [IUA/UA/M3UA/SUA]
ASP Traffic Maintenance (ASPTM) Messages [IUA/UA/M3UA/SUA]
Q.921/Q.931 Boundary Primitives Transport (QPTM)
MTP2 User Adaptation (MAUP) Messages [UA]
Connectionless Messages [SUA]
Connection-Oriented Messages [SUA]
Routing Key Management (RKM) Messages (M3UA)
Interface Identifier Management (IIM) Messages (UA)
"
<category: 'OsmoNetwork-M2UA'>
<comment: 'I hold the mapping from M2UA constants to their
numeric representation.'>
UAConstants class >> clsMgmt [ <category: 'constants'> ^ 0 ]
UAConstants class >> clsTrans [ <category: 'constants'> ^ 1 ]
UAConstants class >> clsSSMN [ <category: 'constants'> ^ 2 ]
UAConstants class >> clsASPSM [ <category: 'constants'> ^ 3 ]
UAConstants class >> clsASPTM [ <category: 'constants'> ^ 4 ]
UAConstants class >> clsQPTM [ <category: 'constants'> ^ 5 ]
UAConstants class >> clsMAUP [ <category: 'constants'> ^ 6 ]
UAConstants class >> clsSUA_LESS [ <category: 'constants'> ^ 7 ]
UAConstants class >> clsSUA_CONN [ <category: 'constants'> ^ 8 ]
UAConstants class >> clsRKM [ <category: 'constants'> ^ 9 ]
UAConstants class >> clasIIM [ <category: 'constants'> ^ 10 ]
UAConstants class >> maupReserved [ <category: 'constants'> ^ 0 ]
UAConstants class >> maupData [ <category: 'constants'> ^ 1 ]
UAConstants class >> maupEstReq [ <category: 'constants'> ^ 2 ]
UAConstants class >> maupEstCon [ <category: 'constants'> ^ 3 ]
UAConstants class >> maupRelReq [ <category: 'constants'> ^ 4 ]
UAConstants class >> maupRelCon [ <category: 'constants'> ^ 5 ]
UAConstants class >> maupRelInd [ <category: 'constants'> ^ 6 ]
UAConstants class >> maupStateReq [ <category: 'constants'> ^ 7 ]
UAConstants class >> maupStateCon [ <category: 'constants'> ^ 8 ]
UAConstants class >> maupStateInd [ <category: 'constants'> ^ 9 ]
UAConstants class >> maupDRetrReq [ <category: 'constants'> ^ 10 ]
UAConstants class >> maupDRetrCon [ <category: 'constants'> ^ 11 ]
UAConstants class >> maupDRetrInd [ <category: 'constants'> ^ 12 ]
UAConstants class >> maupDRetrCompl [ <category: 'constants'> ^ 13 ]
UAConstants class >> maupCongInd [ <category: 'constants'> ^ 14 ]
UAConstants class >> maupDataAck [ <category: 'constants'> ^ 15 ]
UAConstants class >> aspsmReserved [ <category: 'constants'> ^ 0 ]
UAConstants class >> aspsmUp [ <category: 'constants'> ^ 1 ]
UAConstants class >> aspsmDown [ <category: 'constants'> ^ 2 ]
UAConstants class >> aspsmBeat [ <category: 'constants'> ^ 3 ]
UAConstants class >> aspsmUpAck [ <category: 'constants'> ^ 4 ]
UAConstants class >> aspsmDownAck [ <category: 'constants'> ^ 5 ]
UAConstants class >> aspsmBeatAck [ <category: 'constants'> ^ 6 ]
UAConstants class >> asptmReserved [ <category: 'constants'> ^ 0 ]
UAConstants class >> asptmActiv [ <category: 'constants'> ^ 1 ]
UAConstants class >> asptmInactiv [ <category: 'constants'> ^ 2 ]
UAConstants class >> asptmActivAck [ <category: 'constants'> ^ 3 ]
UAConstants class >> asptmInactivAck [ <category: 'constants'> ^ 4 ]
UAConstants class >> mgmtError [ <category: 'constants'> ^ 0 ]
UAConstants class >> mgmtNtfy [ <category: 'constants'> ^ 1 ]
UAConstants class >> iimReserved [ <category: 'constants'> ^ 0 ]
UAConstants class >> iimRegReq [ <category: 'constants'> ^ 1 ]
UAConstants class >> iimRegRsp [ <category: 'constants'> ^ 2 ]
UAConstants class >> iimDeregReq [ <category: 'constants'> ^ 3 ]
UAConstants class >> iimDeregResp [ <category: 'constants'> ^ 4 ]
UAConstants class >> tagReserved [ <category: 'constants'> ^ 0 ]
UAConstants class >> tagIdentInt [ <category: 'constants'> ^ 1 ]
UAConstants class >> tagUnused1 [ <category: 'constants'> ^ 2 ]
UAConstants class >> tagIdentText [ <category: 'constants'> ^ 3 ]
UAConstants class >> tagInfo [ <category: 'constants'> ^ 4 ]
UAConstants class >> tagUnused2 [ <category: 'constants'> ^ 5 ]
UAConstants class >> tagUnused3 [ <category: 'constants'> ^ 6 ]
UAConstants class >> tagDiagInf [ <category: 'constants'> ^ 7 ]
UAConstants class >> tagIdentRange [ <category: 'constants'> ^ 8 ]
UAConstants class >> tagBeatData [ <category: 'constants'> ^ 9 ]
UAConstants class >> tagUnused4 [ <category: 'constants'> ^ 10 ]
UAConstants class >> tagTraMode [ <category: 'constants'> ^ 11 ]
UAConstants class >> tagErrCode [ <category: 'constants'> ^ 12 ]
UAConstants class >> tagStatus [ <category: 'constants'> ^ 13 ]
UAConstants class >> tagUnused5 [ <category: 'constants'> ^ 14 ]
UAConstants class >> tagUnused6 [ <category: 'constants'> ^ 15 ]
UAConstants class >> tagUnused7 [ <category: 'constants'> ^ 16 ]
UAConstants class >> tagAspIdent [ <category: 'constants'> ^ 17 ]
UAConstants class >> tagUnused8 [ <category: 'constants'> ^ 18 ]
UAConstants class >> tagCorrelId [ <category: 'constants'> ^ 19 ]
]
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 ]
]
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 %1 bytes' % {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).
].
]
]
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.'>
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.
]
msgClass [
<category: 'accessing'>
^ msg_class
]
msgType [
<category: 'accessing'>
^ msg_type
]
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 [
| version spare len end |
<category: 'parsing'>
version := aStream next.
version = M2UAConstants version ifFalse: [
self logError: 'M2UA version is wrong %1.' % {version} area: #m2ua.
self error: 'M2UA version is wrong %1.' % {version}.
].
spare := aStream next.
spare = M2UAConstants spare ifFalse: [
self logError: 'M2UA spare is wrong %1.' % {spare} area: #m2ua.
self error: 'M2UA spare is wrong %1.' % {spare}.
].
msg_class := aStream next.
msg_type := aStream next.
len := ((aStream next: 4) uintAt: 1) swap32.
aStream size - aStream position < (len - 8) ifTrue: [
self logError: 'M2UA length is not plausible %1 %2.'
% {len. aStream size - aStream position} area: #m2ua.
self error: 'M2UA length is not plausible %1 %2.'
% {len. aStream size - aStream position}.
].
tags := OrderedCollection new.
end := aStream position + len - 8.
[aStream position < end] whileTrue: [
tags add: (M2UATag fromStream: aStream)
].
]
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.
]
]
"
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));
"
#endif

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,449 @@
"
(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 extend [
subclassResponsibility [
<category: '*-OsmoCore-message'>
thisContext backtrace printNl.
SystemExceptions.SubclassResponsibility signal
]
]
"
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: MSGStructure [
| type fields |
<category: 'OsmoNetwork-MSG'>
<comment: 'Attempt to have a DSL for messages'>
MSGStructure class >> initWith: aType [
<category: 'creation'>
^ self new
instVarNamed: #type put: aType; yourself
]
MSGStructure class >> findStructure: aType [
<category: 'creation'>
self allSubclassesDo: [:each | | struct |
struct := each structure.
struct type = aType ifTrue: [
^ struct
]
].
^ self error: 'Can not find structure for type: %1' % {aType.}
]
MSGStructure class >> decodeByteStream: aStream type: aType [
| structure |
<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."
structure := self findStructure: aType.
^ structure decodeByteStream: aStream.
]
MSGStructure class >> encodeCollection: aCollection type: aType [
| structure |
<category: 'encoding'>
"This is a generic encoding method that will put the collection
onto a MessageBuffer class."
structure := self findStructure: aType.
^ structure 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 %1 but was %2.' % {clazz. 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 %1 but was %2.' % {clazz. 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 %1 but was %2.' % {clazz. 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 structure 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. %1 < %2' % {aLength. self octalLength}.
].
self maxLength ifNotNil: [
aLength > self maxLength ifTrue: [
^ self error: 'The data is too long %1 > %2.' % {aLength. 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 ]
]

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

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

1171
osmo-st-network/SCCP.st Normal file

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,117 @@
"
(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/>.
"
PackageLoader
fileInPackage: #Sockets;
fileInPackage: #OsmoCore.
Object subclass: OsmoUDPSocket [
| socket queue rx tx net_exit name on_data |
<category: 'Osmo-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 := [
[Processor activeProcess name: name, ' RX'.
self runRXProcess] ensure: [net_exit signal]] fork.
"Send data to the MGWs"
tx := [
[Processor activeProcess name: name, ' TX'.
self runTXProcess] 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
]
]

285
osmo-st-network/TLV.st Normal file
View File

@ -0,0 +1,285 @@
"
(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: 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 [
"Kind"
optional [
<category: 'presence'>
^ #optional
]
mandatory [
<category: 'presence'>
^ #mandatory
]
conditional [
<category: 'presence'>
^ #conditional
]
"Type"
tagLengthValue [
<category: 'type'>
^ #tlv
]
tagValue [
<category: 'type'>
^ #tv
]
valueOnly [
<category: 'type'>
^ #valueOnly
]
tagOnly [
<category: 'type'>
^ #tagOnly
]
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
]
isLen16 [
<category: 'access'>
^ self hasLength and: [len_size = 2]
]
isLen8 [
<category: 'access'>
^ self hasLength and: [len_size = 1]
]
isForcedTag [
<category: 'access'>
^ force_tag
]
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
]
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 %1 element is missing' % {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: [
aMsg
putByte: attr tag.
val writeOn: aMsg with: attr.
].
]
]
]

View File

@ -0,0 +1,44 @@
"
(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/>.
"
TestCase subclass: TLVDescriptionTest [
<category: 'BTS-OML-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
]
]

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

@ -0,0 +1,319 @@
"
(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 [
SCCPTests class >> packageNamesUnderTest [
<category: 'accessing'>
^ #('OsmoNetwork')
]
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.
msg printNl.
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.
]
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 poi: 7.
calling := SCCPAddress createWith: 254 poi: 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 poi = 7.
self assert: udt callingAddr ssn = 254.
self assert: udt callingAddr poi = 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 = SCCPGTI npISDN.
self assert: gti nature = SCCPGTI naiInternationalNumber.
self assert: gti addr = '3548900073'.
parsed gtiFromAddr: gti.
self assert: parsed asByteArray = addr.
]
]
TestCase subclass: MessageBufferTest [
testAdd [
| msg1 msg2 msg3 msg_master |
msg1 := MessageBuffer new.
msg2 := MessageBuffer new.
msg3 := MessageBuffer new.
msg1 putByteArray: #(1 2 3) asByteArray.
msg2 putByteArray: #(4 5 6) asByteArray.
msg3 putByteArray: #(7 8 9) asByteArray.
msg_master := MessageBuffer new.
msg_master putByteArray: msg1.
msg_master putByteArray: msg2.
msg_master putByteArray: msg3.
self assert: msg_master size = 9.
self assert: msg_master toByteArray = #(1 2 3 4 5 6 7 8 9) asByteArray.
self assert: msg_master asByteArray = #(1 2 3 4 5 6 7 8 9) asByteArray.
]
testEmptyByteArray [
| msg |
msg := MessageBuffer new.
msg putByteArray: ByteArray new.
self assert: msg size = 0.
self assert: msg toByteArray = #() asByteArray.
]
]
TestCase subclass: M2UATests [
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.
]
]
TestCase subclass: OsmoUDPSocketTest [
testSocketCreation [
| socket rx tx |
socket := OsmoUDPSocket new
name: 'Test Socket';
start: Sockets.DatagramSocket new;
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,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,328 @@
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}.
].
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 >> structure [
<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 >> structure [
<category: ''field''>
^ (super structure)
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,38 @@
<package>
<name>OsmoNetwork</name>
<namespace>Osmo</namespace>
<prereq>OsmoLogging</prereq>
<filein>Extensions.st</filein>
<filein>MessageStructure.st</filein>
<filein>ISUP.st</filein>
<filein>isup_generated.st</filein>
<filein>ISUPExtensions.st</filein>
<filein>IPAConstants.st</filein>
<filein>IPADispatcher.st</filein>
<filein>IPAMuxer.st</filein>
<filein>IPAProtoHandler.st</filein>
<filein>IPAMsg.st</filein>
<filein>MessageBuffer.st</filein>
<filein>SCCP.st</filein>
<filein>M2UA.st</filein>
<filein>LogAreas.st</filein>
<filein>SocketBase.st</filein>
<filein>TLV.st</filein>
<test>
<sunit>Osmo.SCCPTests</sunit>
<sunit>Osmo.IPATests</sunit>
<sunit>Osmo.IPAMsgTests</sunit>
<sunit>Osmo.MessageBufferTest</sunit>
<sunit>Osmo.M2UATests</sunit>
<sunit>Osmo.ISUPGeneratedTest</sunit>
<sunit>Osmo.OsmoUDPSocketTest</sunit>
<sunit>Osmo.TLVDescriptionTest</sunit>
<filein>Tests.st</filein>
<filein>ISUPTests.st</filein>
<filein>IPATests.st</filein>
<filein>TLVTests.st</filein>
</test>
</package>