1
0
Fork 0

m2ua: Move the code to separate directory to prepare merging with Pharo

This commit is contained in:
Holger Hans Peter Freyther 2013-06-17 14:19:26 +02:00
parent a0eb175b26
commit 372c2e0f0b
8 changed files with 484 additions and 424 deletions

View File

@ -42,7 +42,10 @@ ISUP = \
isup/ISUPTests.st
UA = \
ua/M2UA.st ua/M2UAStates.st
ua/XUA.st
M2UA = \
m2ua/M2UAConstants.st m2ua/M2UAMSG.st m2ua/M2UATag.st m2ua/M2UAStates.st
OSMO = \
osmo/LogAreaOsmo.st \
@ -62,7 +65,7 @@ all:
convert:
$(GST_CONVERT) $(CONVERT_RULES) -F squeak -f gst \
-o fileout.st pharo-porting/compat_for_pharo.st \
$(CORE) $(IPA) $(SCCP) $(ISUP) $(UA) $(OSMO) $(MTP3) \
$(CORE) $(IPA) $(SCCP) $(ISUP) $(UA) $(OSMO) $(MTP3) $(M2UA) \
Tests.st pharo-porting/changes_for_pharo.st
sed -i s,"=>","==>",g fileout.st

126
m2ua/M2UAConstants.st Normal file
View File

@ -0,0 +1,126 @@
"
(C) 2011-2013 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
UAConstants subclass: M2UAConstants [
<category: 'OsmoNetwork-M2UA'>
<comment: 'I hold the M2UA specific constants'>
M2UAConstants class >> version [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> spare [ <category: 'constants'> ^ 0 ]
M2UAConstants class >> tagData [ <category: 'constants'> ^ 768 ]
M2UAConstants class >> tagDataTTC [ <category: 'constants'> ^ 769 ]
M2UAConstants class >> tagStateReq [ <category: 'constants'> ^ 770 ]
M2UAConstants class >> tagStateEvent [ <category: 'constants'> ^ 771 ]
M2UAConstants class >> tagCongStatus [ <category: 'constants'> ^ 772 ]
M2UAConstants class >> tagDiscStatus [ <category: 'constants'> ^ 773 ]
M2UAConstants class >> tagAction [ <category: 'constants'> ^ 774 ]
M2UAConstants class >> tagSeqNo [ <category: 'constants'> ^ 775 ]
M2UAConstants class >> tagRetrRes [ <category: 'constants'> ^ 776 ]
M2UAConstants class >> tagLinkKey [ <category: 'constants'> ^ 777 ]
M2UAConstants class >> tagLocLinkeyIdent [ <category: 'constants'> ^ 778 ]
M2UAConstants class >> tagSDT [ <category: 'constants'> ^ 779 ]
M2UAConstants class >> tagSDL [ <category: 'constants'> ^ 780 ]
M2UAConstants class >> tagRegRes [ <category: 'constants'> ^ 781 ]
M2UAConstants class >> tagRegStatus [ <category: 'constants'> ^ 782 ]
M2UAConstants class >> tagDeregRes [ <category: 'constants'> ^ 783 ]
M2UAConstants class >> tagDeregStatus [ <category: 'constants'> ^ 784 ]
M2UAConstants class >> statusLpoSet [ <category: 'constants'> ^ 0 ]
M2UAConstants class >> statusLpoClear [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> statusEmergSet [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> statusEmergClear [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> statusFlushBufs [ <category: 'constants'> ^ 4 ]
M2UAConstants class >> statusContinue [ <category: 'constants'> ^ 5 ]
M2UAConstants class >> statusClearRTB [ <category: 'constants'> ^ 6 ]
M2UAConstants class >> statusAudit [ <category: 'constants'> ^ 7 ]
M2UAConstants class >> statusCongCleared[ <category: 'constants'> ^ 8 ]
M2UAConstants class >> statusCongAccept [ <category: 'constants'> ^ 9 ]
M2UAConstants class >> statusCongDisc [ <category: 'constants'> ^ 10 ]
M2UAConstants class >> eventRPOEnter [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> eventRPOExit [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> eventLPOEnter [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> eventLPOExit [ <category: 'constants'> ^ 4 ]
M2UAConstants class >> congLevelNone [ <category: 'constants'> ^ 0 ]
M2UAConstants class >> congLevel1 [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> congLevel2 [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> congLevel3 [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> actionRtrvBSN [ <category: 'constants'> ^ 0 ]
M2UAConstants class >> actionRtrvMSGs [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> resultSuccess [ <category: 'constants'> ^ 0 ]
M2UAConstants class >> resultFailure [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> traOverride [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> traLoadShare [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> traBroadcast [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> errInvalidVersion [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> errInvalidIdent [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> errUnsMsgClass [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> errUnsMsgType [ <category: 'constants'> ^ 4 ]
M2UAConstants class >> errUnsTraMode [ <category: 'constants'> ^ 5 ]
M2UAConstants class >> errUneMsg [ <category: 'constants'> ^ 6 ]
M2UAConstants class >> errProtocolError [ <category: 'constants'> ^ 7 ]
M2UAConstants class >> errUnsInterIdentInt [ <category: 'constants'> ^ 8 ]
M2UAConstants class >> errInvalidStreamIdent[ <category: 'constants'> ^ 9 ]
M2UAConstants class >> errUnsued1 [ <category: 'constants'> ^ 10 ]
M2UAConstants class >> errUnsued2 [ <category: 'constants'> ^ 11 ]
M2UAConstants class >> errUnsued3 [ <category: 'constants'> ^ 12 ]
M2UAConstants class >> errRefused [ <category: 'constants'> ^ 13 ]
M2UAConstants class >> errAspIdentRequired [ <category: 'constants'> ^ 14 ]
M2UAConstants class >> errInvalidAspIdent [ <category: 'constants'> ^ 15 ]
M2UAConstants class >> errAspActForIdent [ <category: 'constants'> ^ 16 ]
M2UAConstants class >> errInvalidParamVal [ <category: 'constants'> ^ 17 ]
M2UAConstants class >> errParamFieldError [ <category: 'constants'> ^ 18 ]
M2UAConstants class >> errUnexpParam [ <category: 'constants'> ^ 19 ]
M2UAConstants class >> errUnused4 [ <category: 'constants'> ^ 20 ]
M2UAConstants class >> errUnused5 [ <category: 'constants'> ^ 21 ]
M2UAConstants class >> errMissingParam [ <category: 'constants'> ^ 22 ]
M2UAConstants class >> ntfyKindStateChange [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> ntfyKindOther [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> ntfyStateASInactive [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> ntfyStateASActive [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> ntfyStateASPending [ <category: 'constants'> ^ 4 ]
M2UAConstants class >> ntfyOtherInsuffRes [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> ntfyOtherAltAspActiv [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> ntfyOtherAspFailure [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> regSuccess [ <category: 'constants'> ^ 0 ]
M2UAConstants class >> regErrorUnknown [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> regErrorInvSDLI [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> regErrorInvSDTI [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> regErrorInvLinkKey [ <category: 'constants'> ^ 4 ]
M2UAConstants class >> regErrorPermDenied [ <category: 'constants'> ^ 5 ]
M2UAConstants class >> regErrorOverlapKey [ <category: 'constants'> ^ 6 ]
M2UAConstants class >> regErrorNotProvisioned [ <category: 'constants'> ^ 7 ]
M2UAConstants class >> regErrorInsuffRes [ <category: 'constants'> ^ 8 ]
M2UAConstants class >> deregSuccess [ <category: 'constants'> ^ 0 ]
M2UAConstants class >> deregErrorUnknown [ <category: 'constants'> ^ 1 ]
M2UAConstants class >> deregErrorInvIdent [ <category: 'constants'> ^ 2 ]
M2UAConstants class >> deregErrorPermDenied [ <category: 'constants'> ^ 3 ]
M2UAConstants class >> deregErrorNotReg [ <category: 'constants'> ^ 4 ]
]

147
m2ua/M2UAMSG.st Normal file
View File

@ -0,0 +1,147 @@
"
(C) 2011-2013 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
Object subclass: M2UAMSG [
| msg_class msg_type tags |
<category: 'OsmoNetwork-M2UA'>
<comment: 'I can parse a M2UA message from the wire, allow you
to see the class, type and include tags. In C the structure will
look like this:
struct m2ua_common_hdr {
uint8_t version;
uint8_t spare;
uint8_t msg_class;
uint8_t msg_type;
uint32_t msg_length;
uint8_t data[0];
} __attribute__((packed));
struct m2ua_parameter_hdr {
uint16_t tag;
uint16_t len;
uint8_t data[0];
} __attribute__((packed));
'>
M2UAMSG class >> parseFrom: aMsg [
<category: 'parsing'>
self logDataContext: aMsg area: #m2ua.
^ self new
parseFrom: aMsg readStream;
yourself.
]
M2UAMSG class >> fromClass: aClass type: aType [
<category: 'parsing'>
^ self new
instVarNamed: #msg_class put: aClass;
instVarNamed: #msg_type put: aType;
yourself.
]
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 <1p>.' expandMacrosWith: version) area: #m2ua.
self error: ('M2UA version is wrong <1p>.' expandMacrosWith: version).
].
spare := aStream next.
spare = M2UAConstants spare ifFalse: [
self logError: ('M2UA spare is wrong <1p>.' expandMacrosWith: spare) area: #m2ua.
self error: ('M2UA spare is wrong <1p>.' expandMacrosWith: spare).
].
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 <1p> <2p>.'
expandMacrosWith: len with: aStream size - aStream position)
area: #m2ua.
self error: ('M2UA length is not plausible <1p> <2p>.'
expandMacrosWith: len with: aStream size - aStream position).
].
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.
]
]

85
m2ua/M2UATag.st Normal file
View File

@ -0,0 +1,85 @@
"
(C) 2011-2013 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
Object subclass: M2UATag [
| tag_nr data |
<category: 'OsmoNetwork-M2UA'>
<comment: 'I represent a tag of a M2UA packet. I hold the
number of the tag and the data associated with it.'>
M2UATag class >> fromStream: aStream [
<category: 'parsing'>
^ self new
parseFrom: aStream
]
M2UATag class >> initWith: aTag data: aData [
<category: 'creation'>
^ self new
instVarNamed: #tag_nr put: aTag;
instVarNamed: #data put: aData;
yourself
]
parseFrom: aStream [
| len padding |
<category: 'parsing'>
tag_nr := ((aStream next: 2) shortAt: 1) swap16.
len := ((aStream next: 2) shortAt: 1) swap16.
data := aStream next: len - 4.
padding := len \\ 4.
padding > 0 ifTrue: [
self logNotice:
('Going to skip <1p> bytes' expandMacrosWith: 4 - padding) area: #m2ua.
aStream skip: 4 - padding.
].
]
nr [
<category: 'accessing'>
^ tag_nr
]
data [
<category: 'accessing'>
^ data ifNil: [data := ByteArray new]
]
writeOn: aMsg [
| rest |
<category: 'private'>
aMsg putLen16: tag_nr.
aMsg putLen16: self data size + 4.
aMsg putByteArray: self data.
rest := self data size \\ 4.
rest > 0 ifTrue: [
aMsg putByteArray: (ByteArray new: 4 - rest).
].
]
isTag: aNr [
<category: 'accessing'>
^ self nr = aNr
]
]

View File

@ -27,8 +27,11 @@
<filein>sccp/SCCPGlobalTitle.st</filein>
<filein>sccp/SCCPGlobalTitleTranslation.st</filein>
<filein>mtp3/MTP3Messages.st</filein>
<filein>ua/M2UA.st</filein>
<filein>ua/M2UAStates.st</filein>
<filein>ua/XUA.st</filein>
<filein>m2ua/M2UAConstants.st</filein>
<filein>m2ua/M2UAStates.st</filein>
<filein>m2ua/M2UATag.st</filein>
<filein>m2ua/M2UAMSG.st</filein>
<filein>osmo/LogAreaOsmo.st</filein>
<filein>osmo/OsmoUDPSocket.st</filein>
<filein>osmo/OsmoCtrlLogging.st</filein>

View File

@ -1,420 +0,0 @@
"
(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 [
"
"
<category: 'OsmoNetwork-M2UA'>
<comment: 'I hold the mapping from M2UA constants to their
numeric representation. The following classes are defined:
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)
'>
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 <1p> bytes' expandMacrosWith: 4 - padding) area: #m2ua.
aStream skip: 4 - padding.
].
]
nr [
<category: 'accessing'>
^ tag_nr
]
data [
<category: 'accessing'>
^ data ifNil: [data := ByteArray new]
]
writeOn: aMsg [
| rest |
<category: 'private'>
aMsg putLen16: tag_nr.
aMsg putLen16: self data size + 4.
aMsg putByteArray: self data.
rest := self data size \\ 4.
rest > 0 ifTrue: [
aMsg putByteArray: (ByteArray new: 4 - rest).
].
]
isTag: aNr [
<category: 'accessing'>
^ self nr = aNr
]
]
Object subclass: M2UAMSG [
| msg_class msg_type tags |
<category: 'OsmoNetwork-M2UA'>
<comment: 'I can parse a M2UA message from the wire, allow you
to see the class, type and include tags. In C the structure will
look like this:
struct m2ua_common_hdr {
uint8_t version;
uint8_t spare;
uint8_t msg_class;
uint8_t msg_type;
uint32_t msg_length;
uint8_t data[0];
} __attribute__((packed));
struct m2ua_parameter_hdr {
uint16_t tag;
uint16_t len;
uint8_t data[0];
} __attribute__((packed));
'>
M2UAMSG class >> parseFrom: aMsg [
<category: 'parsing'>
self logDataContext: aMsg area: #m2ua.
^ self new
parseFrom: aMsg readStream;
yourself.
]
M2UAMSG class >> fromClass: aClass type: aType [
<category: 'parsing'>
^ self new
instVarNamed: #msg_class put: aClass;
instVarNamed: #msg_type put: aType;
yourself.
]
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 <1p>.' expandMacrosWith: version) area: #m2ua.
self error: ('M2UA version is wrong <1p>.' expandMacrosWith: version).
].
spare := aStream next.
spare = M2UAConstants spare ifFalse: [
self logError: ('M2UA spare is wrong <1p>.' expandMacrosWith: spare) area: #m2ua.
self error: ('M2UA spare is wrong <1p>.' expandMacrosWith: spare).
].
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 <1p> <2p>.'
expandMacrosWith: len with: aStream size - aStream position)
area: #m2ua.
self error: ('M2UA length is not plausible <1p> <2p>.'
expandMacrosWith: len with: aStream size - aStream position).
].
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.
]
]

116
ua/XUA.st Normal file
View File

@ -0,0 +1,116 @@
"
(C) 2011-2012 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
Object subclass: UAConstants [
"
"
<category: 'OsmoNetwork-M2UA'>
<comment: 'I hold the mapping from M2UA constants to their
numeric representation. The following classes are defined:
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)
'>
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 ]
]