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

misc: Clean up the categories of the network module

This commit is contained in:
Holger Hans Peter Freyther 2011-09-27 16:27:34 +02:00
parent d7b2323602
commit ca50ffe022
13 changed files with 384 additions and 10 deletions

View File

@ -21,6 +21,8 @@ PackageLoader fileInPackage: 'Sockets'.
Integer extend [
swap16 [
| tmp |
<category: '*-OsmoCore-message'>
tmp := self bitAnd: 16rFFFF.
^ (tmp bitShift: -8) bitOr: ((tmp bitAnd: 16rFF) bitShift: 8)
]
@ -28,6 +30,7 @@ Integer extend [
swap32 [
| tmp |
"Certainly not the most effective way"
<category: '*-OsmoCore-message'>
tmp := 0.
tmp := tmp bitOr: ((self bitAnd: 16rFF000000) bitShift: -24).
@ -42,18 +45,21 @@ Integer extend [
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
]
]
@ -63,15 +69,14 @@ ByteArray extend [
Sockets.Socket extend [
nextUshort [
"Return the next 2 bytes in the byte array, interpreted as a 16 bit unsigned int"
<category: 'binary I/O'>
<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: 'private'>
<category: '*-OsmoCore-message'>
| int msb |
int := 0.
0 to: n * 8 - 16
@ -85,7 +90,7 @@ Sockets.Socket extend [
nextByte [
"Return the next byte in the file, or nil at eof"
<category: 'basic'>
<category: '*-OsmoCore-message'>
| a |
a := self next.
^a isNil ifTrue: [a] ifFalse: [a asInteger]
@ -94,7 +99,7 @@ Sockets.Socket extend [
ByteArray extend [
castTo: type [
<category: 'private'>
<category: '*-OsmoCore-message'>
^ (CObject new storage: self) castTo: type
]
]

View File

@ -17,6 +17,8 @@
"
Object subclass: IPAConstants [
<category: 'OsmoNetwork-IPA'>
IPAConstants class >> protocolRSL [ ^ 16r00 ]
IPAConstants class >> protocolMGCP [ ^ 16rFC ]
IPAConstants class >> protocolSCCP [ ^ 16rFD ]
@ -52,6 +54,8 @@ Object subclass: IPAConstants [
]
CPackedStruct subclass: IPASCCPState [
<category: 'OsmoNetwork-IPA'>
<declaration: #(
#(#src (#array #byte 3))
#(#dst (#array #byte 3))

View File

@ -19,6 +19,7 @@
Object subclass: IPADispatcher [
| handlers |
<category: 'OsmoNetwork-IPA'>
<comment: 'I am a hub and one can register handlers for the streams'>
initialize [

View File

@ -19,6 +19,8 @@
Object subclass: IPADemuxer [
| socket |
<category: 'OsmoNetwork-IPA'>
IPADemuxer class >> initOn: aSocket [
^ (self new)
socket: aSocket;
@ -51,6 +53,8 @@ Object subclass: IPADemuxer [
Object subclass: IPAMuxer [
| socket |
<category: 'OsmoNetwork-IPA'>
IPAMuxer class >> initOn: aSocket [
^ (self new)
socket: aSocket;

View File

@ -18,8 +18,9 @@
Object subclass: IPAProtoHandler [
| token muxer |
<comment: 'I handle the IPA protocol'>
<category: 'osmo-networking'>
<category: 'OsmoNetwork-IPA'>
handlers := nil.

View File

@ -18,6 +18,7 @@
Object subclass: ISUPConstants [
<comment: 'Constants for the ISDN User Part (ISUP) protocol'>
<category: 'OsmoNetwork-ISUP'>
ISUPConstants class [
msgAPT [ ^ 2r01000001 ] " Application transport"
@ -181,6 +182,7 @@ Object subclass: ISUPConstants [
MSGStructure subclass: ISUPMessage [
<comment: 'I am the base class for the ISUP messages'>
<category: 'OsmoNetwork-ISUP'>
parseVariable: aStream with: aClass into: decoded [
| pos ptr res |

View File

@ -17,6 +17,8 @@
"
Osmo.LogArea subclass: LogAreaSCCP [
<category: 'OsmoNetwork-SCCP'>
LogAreaSCCP class >> areaName [ ^ #sccp ]
LogAreaSCCP class >> areaDescription [ ^ 'SCCP related' ]
LogAreaSCCP class >> default [
@ -28,6 +30,8 @@ Osmo.LogArea subclass: LogAreaSCCP [
]
Osmo.LogArea subclass: LogAreaIPA [
<category: 'OsmoNetwork-IPA'>
LogAreaIPA class >> areaName [ ^ #ipa ]
LogAreaIPA class >> areaDescription [ ^ 'IPA related' ]
LogAreaIPA class >> default [
@ -39,6 +43,8 @@ Osmo.LogArea subclass: LogAreaIPA [
]
Osmo.LogArea subclass: LogAreaM2UA [
<category: 'OsmoNetwork-M2UA'>
LogAreaM2UA class >> areaName [ ^ #m2ua ]
LogAreaM2UA class >> areaDescription [ ^ 'MTP2 User Adaption' ]
LogAreaM2UA class >> default [

View File

@ -31,6 +31,8 @@ Object subclass: UAConstants [
Interface Identifier Management (IIM) Messages (UA)
"
<category: 'OsmoNetwork-M2UA'>
UAConstants class >> clsMgmt [ ^ 0 ]
UAConstants class >> clsTrans [ ^ 1 ]
UAConstants class >> clsSSMN [ ^ 2 ]
@ -108,6 +110,7 @@ Object subclass: UAConstants [
]
UAConstants subclass: M2UAConstants [
<category: 'OsmoNetwork-M2UA'>
<comment: 'I hold the M2UA specific constants'>
M2UAConstants class >> version [ ^ 1 ]
@ -218,6 +221,8 @@ UAConstants subclass: M2UAConstants [
Object subclass: M2UATag [
| tag_nr data |
<category: 'OsmoNetwork-M2UA'>
M2UATag class >> fromStream: aStream [
^ self new
parseFrom: aStream
@ -271,6 +276,8 @@ Object subclass: M2UATag [
Object subclass: M2UAMSG [
| msg_class msg_type tags |
<category: 'OsmoNetwork-M2UA'>
M2UAMSG class >> parseFrom: aMsg [
self logDataContext: aMsg area: #m2ua.

View File

@ -18,6 +18,8 @@
Collection subclass: MessageBuffer [
| chunks |
<category: 'OsmoNetwork-Message'>
<comment: 'A network buffer/creation class. Modeled after the msgb of osmocore'>
MessageBuffer class >> new [

View File

@ -24,6 +24,8 @@ 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 [
@ -203,7 +205,8 @@ Object subclass: MSGStructure [
Object subclass: MSGField [
| data |
<category: 'osmo-networking'>
<category: 'OsmoNetwork-MSG'>
<comment: 'The description of an Information Element'>
MSGField class >> readVariableFrom: aStream length: aLength [
@ -271,6 +274,8 @@ Object subclass: MSGField [
]
MSGField subclass: MSGFixedField [
<category: 'OsmoNetwork-MSG'>
MSGFixedField class >> isVarible [ ^ false ]
MSGFixedField class >> isFixed [ ^ true ]
@ -290,6 +295,8 @@ MSGField subclass: MSGFixedField [
]
MSGField subclass: MSGVariableField [
<category: 'OsmoNetwork-MSG'>
MSGVariableField class >> isVarible [ ^ true ]
MSGVariableField class >> isFixed [ ^ false ]
]

35
SCCP.st
View File

@ -17,7 +17,8 @@
"
Object subclass: SCCPHelper [
<category: 'osmo-network'>
<category: 'OsmoNetwork-SCCP'>
SCCPHelper class >> msgCr [ ^ 16r01 ]
SCCPHelper class >> msgCc [ ^ 16r02 ]
SCCPHelper class >> msgCref [ ^ 16r03 ]
@ -61,6 +62,8 @@ Object subclass: SCCPHelper [
Object subclass: SCCPPNC [
| dict |
<category: 'OsmoNetwork-SCCP'>
SCCPPNC class >> parseFrom: aPnc [
| dict pnc |
@ -123,6 +126,8 @@ Object subclass: SCCPPNC [
Object subclass: SCCPGTI [
| indicator nai data |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the Global Title of Q.713.'>
"gti indicator in the Addr header"
@ -224,6 +229,9 @@ Object subclass: SCCPGTI [
SCCPGTI subclass: SCCPGTITranslation [
| trans plan enc nature addr |
<category: 'OsmoNetwork-SCCP'>
SCCPGTITranslation class >> subType [ ^ 4 ]
SCCPGTITranslation class >> initWith: data [
| enc |
@ -284,6 +292,8 @@ SCCPGTI subclass: SCCPGTITranslation [
Object subclass: SCCPAddress [
| route_ssn ssn poi gti gti_ind |
<category: 'OsmoNetwork-SCCP'>
SCCPAddress class >> ssnNotKnown [ ^ 0 ]
SCCPAddress class >> ssnSCCPMgnt [ ^ 1 ]
SCCPAddress class >> ssnITURsrvd [ ^ 2 ]
@ -446,7 +456,9 @@ Object subclass: SCCPAddress [
]
Object subclass: SCCPAddrReference [
<category: 'osmo-network'>
<category: 'OsmoNetwork-SCCP'>
SCCPAddrReference class >> store: anAddress on: aMsg [
"Store the threee bytes of an sccp address on a messagebuffer"
@ -478,6 +490,8 @@ Object subclass: SCCPAddrReference [
]
Object subclass: SCCPMessage [
<category: 'OsmoNetwork-SCCP'>
SCCPMessage class >> decode: aByteArray [
| type |
type := aByteArray at: 1.
@ -495,9 +509,10 @@ Object subclass: SCCPMessage [
]
SCCPMessage subclass: SCCPConnectionRequest [
<category: 'osmo-network'>
| src dst pnc |
<category: 'OsmoNetwork-SCCP'>
SCCPConnectionRequest class >> msgType [
<category: 'factory'>
^ SCCPHelper msgCr
@ -590,6 +605,9 @@ SCCPMessage subclass: SCCPConnectionRequest [
SCCPMessage subclass: SCCPConnectionConfirm [
| src dst pnc |
<category: 'OsmoNetwork-SCCP'>
SCCPConnectionConfirm class >> msgType [
<category: 'factory'>
^ SCCPHelper msgCc
@ -638,6 +656,8 @@ SCCPMessage subclass: SCCPConnectionConfirm [
SCCPMessage subclass: SCCPConnectionData [
| dst data |
<category: 'OsmoNetwork-SCCP'>
SCCPConnectionData class >> msgType [
<category: 'factory'>
^ SCCPHelper msgDt1
@ -707,6 +727,8 @@ SCCPMessage subclass: SCCPConnectionData [
SCCPMessage subclass: SCCPConnectionReleased [
| src dst cause pnc |
<category: 'OsmoNetwork-SCCP'>
SCCPConnectionReleased class >> msgType [
<category: 'factory'>
^ SCCPHelper msgRlsd
@ -754,6 +776,9 @@ SCCPMessage subclass: SCCPConnectionReleased [
SCCPMessage subclass: SCCPConnectionReleaseComplete [
| dst src |
<category: 'OsmoNetwork-SCCP'>
SCCPConnectionReleaseComplete class >> msgType [
^ SCCPHelper msgRlc.
]
@ -786,6 +811,8 @@ SCCPMessage subclass: SCCPConnectionReleaseComplete [
SCCPMessage subclass: SCCPUDT [
| called calling data error udtClass |
<category: 'OsmoNetwork-SCCP'>
SCCPUDT class >> msgType [
^ SCCPHelper msgUdt
]
@ -885,6 +912,8 @@ SCCPMessage subclass: SCCPUDT [
SCCPMessage subclass: SCCPInactivityTest [
| src dst proto seq credit |
<category: 'OsmoNetwork-SCCP'>
SCCPInactivityTest class >> msgType [
<category: 'factory'>
^ SCCPHelper msgIt

View File

@ -190,6 +190,8 @@ Object subclass: StructCreator [
type :=
'MSGFixedField subclass: %1 [
<category: ''OsmoNetwork-ISUP''>
%1 class >> parameterName [ ^ ''%2'' ]
%1 class >> parameterValue [ ^ ISUPConstants par%3 ]
%1 class >> octalLength [ ^ %4 ]
@ -213,6 +215,8 @@ Object subclass: StructCreator [
type :=
'MSGVariableField subclass: %1 [
<category: ''OsmoNetwork-ISUP''>
%1 class >> parameterName [ ^ ''%2'' ]
%1 class >> parameterValue [ ^ ISUPConstants par%3 ]
%1 class >> octalLength [ ^ %4 ]
@ -228,6 +232,8 @@ Object subclass: StructCreator [
struct isEmpty ifTrue: [
struct add: '
ISUPMessage subclass: ISUP%1 [
<category: ''OsmoNetwork-ISUP''>
ISUP%1 class >> structure [
^ (self initWith: ISUPConstants msg%1)' % {structName. }.
^ true
@ -268,6 +274,8 @@ message type.'>
self structs add: '
ISUP%1 subclass: ISUP%2 [
<category: ''OsmoNetwork-ISUP''>
ISUP%2 class >> structure [
^ (super structure)
type: ISUPConstants msg%2; yourself

File diff suppressed because it is too large Load Diff