1
0
Fork 0

sccp: Move the SCCPAddress to a separate file

Begin with the one class one file pattern and move the SCCPAddress
to a shiny new file.
This commit is contained in:
Holger Hans Peter Freyther 2013-04-02 16:07:42 +02:00
parent 0dd9a2287c
commit 247205d803
4 changed files with 202 additions and 183 deletions

View File

@ -29,7 +29,7 @@ IPA = \
ipa/IPAConstants.st ipa/IPADispatcher.st ipa/IPAMuxer.st \
ipa/IPAProtoHandler.st ipa/IPAMsg.st \
SCCP = sccp/SCCP.st
SCCP = sccp/SCCP.st sccp/SCCPAddress.st
ISUP = \
isup/ISUP.st isup/isup_generated.st isup/ISUPExtensions.st \

View File

@ -22,6 +22,7 @@
<filein>ipa/IPAProtoHandler.st</filein>
<filein>ipa/IPAMsg.st</filein>
<filein>sccp/SCCP.st</filein>
<filein>sccp/SCCPAddress.st</filein>
<filein>ua/M2UA.st</filein>
<filein>osmo/LogAreaOsmo.st</filein>
<filein>osmo/OsmoUDPSocket.st</filein>

View File

@ -336,188 +336,6 @@ SCCPGTI subclass: SCCPGTITranslation [
]
]
Object subclass: SCCPAddress [
| route_ssn ssn poi gti gti_ind |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the SCCP Address including the
SSN, GTI if present.'>
SCCPAddress class >> ssnNotKnown [ <category: 'constants'> ^ 0 ]
SCCPAddress class >> ssnSCCPMgnt [ <category: 'constants'> ^ 1 ]
SCCPAddress class >> ssnITURsrvd [ <category: 'constants'> ^ 2 ]
SCCPAddress class >> ssnISUP [ <category: 'constants'> ^ 3 ]
SCCPAddress class >> ssnOMA [ <category: 'constants'> ^ 4 ]
SCCPAddress class >> ssnMAP [ <category: 'constants'> ^ 5 ]
SCCPAddress class >> ssnHLR [ <category: 'constants'> ^ 6 ]
SCCPAddress class >> ssnVLR [ <category: 'constants'> ^ 7 ]
SCCPAddress class >> ssnMSC [ <category: 'constants'> ^ 8 ]
SCCPAddress class >> ssnEIC [ <category: 'constants'> ^ 9 ]
SCCPAddress class >> ssnAUC [ <category: 'constants'> ^ 10 ]
SCCPAddress class >> ssnISUPSRV [ <category: 'constants'> ^ 11 ]
SCCPAddress class >> ssnReserved [ <category: 'constants'> ^ 12 ]
SCCPAddress class >> ssnBroadISDN[ <category: 'constants'> ^ 13 ]
SCCPAddress class >> ssnTCTest [ <category: 'constants'> ^ 14 ]
SCCPAddress class >> createWith: ssn [
<category: 'creation'>
^ (SCCPAddress new)
ssn: ssn;
routedOnSSN: true;
yourself
]
SCCPAddress class >> createWith: ssn poi: aPoi [
<category: 'creation'>
^ SCCPAddress new
ssn: ssn;
routedOnSSN: true;
poi: aPoi;
yourself
]
SCCPAddress class >> parseFrom: aByteArray [
| routed_ssn gti_ind gti len ai ssn poi dat |
<category: 'parsing'>
poi := nil.
len := aByteArray at: 1.
ai := aByteArray at: 2.
"Copy the address"
dat := aByteArray copyFrom: 3 to: len + 1.
"Point Code"
(ai bitAnd: 1) = 1
ifTrue: [
poi := (dat ushortAt: 1).
dat := dat copyFrom: 3.
].
"SSN"
routed_ssn := (ai bitAnd: 16r40) = 16r40.
ssn := dat at: 1.
dat := dat copyFrom: 2.
"GTI"
gti_ind := (ai bitAnd: 16r3C) bitShift: -2.
gti := dat copyFrom: 1.
^ SCCPAddress new
ssn: ssn;
poi: poi;
routedOnSSN: routed_ssn;
gti: gti indicator: gti_ind;
yourself.
]
routedOnSSN: aFlag [
<category: 'ssn'>
route_ssn := aFlag
]
routedOnSSN [
<category: 'ssn'>
^ route_ssn ifNil: [false]
]
gti [
<category: 'gti'>
^ gti
]
gtiInd [
<category: 'gti'>
^ gti_ind
]
gti: aGti indicator: aGtiInd [
<category: 'gti'>
gti := aGti.
gti_ind := aGtiInd bitAnd: 16rF.
]
gtiAsParsed [
<category: 'gti'>
^ gti_ind = 0
ifTrue: [nil]
ifFalse: [SCCPGTI initWith: gti_ind data: gti].
]
gtiFromAddr: aGti [
<category: 'gti'>
gti_ind := aGti class subType.
gti := aGti asByteArray.
]
poi: aPoi [
<category: 'point-code-indicator'>
poi := aPoi.
]
poi [
<category: 'point-code-indicator'>
^ poi
]
ssn: assn [
<category: 'ssn'>
ssn := assn
]
ssn [
<category: 'accessing'>
^ ssn.
]
asByteArray [
"Most simple address storing routine"
| ai data |
<category: 'encoding'>
data := OrderedCollection new.
"Create the Address Information"
ai := 0.
"SSN indicator"
ai := ai bitOr: 2.
self routedOnSSN ifTrue: [
ai := ai bitOr: 64.
].
"Point Code"
poi ifNotNil: [
ai := ai bitOr: 1.
].
"GTI Indicator"
gti_ind ifNotNil: [
ai := ai bitOr: (gti_ind bitShift: 2).
].
data add: ai.
"POC"
poi ifNotNil: [
data add: ((poi bitAnd: 16r00FF) bitShift: 0).
data add: ((poi bitAnd: 16rFF00) bitShift: -8).
].
"SSN"
data add: ssn.
"GTI"
gti_ind ifNotNil: [
gti do: [:each | data add: each ].
].
data addFirst: data size.
^ data asByteArray
]
]
Object subclass: SCCPAddrReference [
<category: 'OsmoNetwork-SCCP'>

200
sccp/SCCPAddress.st Normal file
View File

@ -0,0 +1,200 @@
"
(C) 2010-2012 by Holger Hans Peter Freyther
All Rights Reserved
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
Object subclass: SCCPAddress [
| route_ssn ssn poi gti gti_ind |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the SCCP Address including the
SSN, GTI if present.'>
SCCPAddress class >> ssnNotKnown [ <category: 'constants'> ^ 0 ]
SCCPAddress class >> ssnSCCPMgnt [ <category: 'constants'> ^ 1 ]
SCCPAddress class >> ssnITURsrvd [ <category: 'constants'> ^ 2 ]
SCCPAddress class >> ssnISUP [ <category: 'constants'> ^ 3 ]
SCCPAddress class >> ssnOMA [ <category: 'constants'> ^ 4 ]
SCCPAddress class >> ssnMAP [ <category: 'constants'> ^ 5 ]
SCCPAddress class >> ssnHLR [ <category: 'constants'> ^ 6 ]
SCCPAddress class >> ssnVLR [ <category: 'constants'> ^ 7 ]
SCCPAddress class >> ssnMSC [ <category: 'constants'> ^ 8 ]
SCCPAddress class >> ssnEIC [ <category: 'constants'> ^ 9 ]
SCCPAddress class >> ssnAUC [ <category: 'constants'> ^ 10 ]
SCCPAddress class >> ssnISUPSRV [ <category: 'constants'> ^ 11 ]
SCCPAddress class >> ssnReserved [ <category: 'constants'> ^ 12 ]
SCCPAddress class >> ssnBroadISDN[ <category: 'constants'> ^ 13 ]
SCCPAddress class >> ssnTCTest [ <category: 'constants'> ^ 14 ]
SCCPAddress class >> createWith: ssn [
<category: 'creation'>
^ (SCCPAddress new)
ssn: ssn;
routedOnSSN: true;
yourself
]
SCCPAddress class >> createWith: ssn poi: aPoi [
<category: 'creation'>
^ SCCPAddress new
ssn: ssn;
routedOnSSN: true;
poi: aPoi;
yourself
]
SCCPAddress class >> parseFrom: aByteArray [
| routed_ssn gti_ind gti len ai ssn poi dat |
<category: 'parsing'>
poi := nil.
len := aByteArray at: 1.
ai := aByteArray at: 2.
"Copy the address"
dat := aByteArray copyFrom: 3 to: len + 1.
"Point Code"
(ai bitAnd: 1) = 1
ifTrue: [
poi := (dat ushortAt: 1).
dat := dat copyFrom: 3.
].
"SSN"
routed_ssn := (ai bitAnd: 16r40) = 16r40.
ssn := dat at: 1.
dat := dat copyFrom: 2.
"GTI"
gti_ind := (ai bitAnd: 16r3C) bitShift: -2.
gti := dat copyFrom: 1.
^ SCCPAddress new
ssn: ssn;
poi: poi;
routedOnSSN: routed_ssn;
gti: gti indicator: gti_ind;
yourself.
]
routedOnSSN: aFlag [
<category: 'ssn'>
route_ssn := aFlag
]
routedOnSSN [
<category: 'ssn'>
^ route_ssn ifNil: [false]
]
gti [
<category: 'gti'>
^ gti
]
gtiInd [
<category: 'gti'>
^ gti_ind
]
gti: aGti indicator: aGtiInd [
<category: 'gti'>
gti := aGti.
gti_ind := aGtiInd bitAnd: 16rF.
]
gtiAsParsed [
<category: 'gti'>
^ gti_ind = 0
ifTrue: [nil]
ifFalse: [SCCPGTI initWith: gti_ind data: gti].
]
gtiFromAddr: aGti [
<category: 'gti'>
gti_ind := aGti class subType.
gti := aGti asByteArray.
]
poi: aPoi [
<category: 'point-code-indicator'>
poi := aPoi.
]
poi [
<category: 'point-code-indicator'>
^ poi
]
ssn: assn [
<category: 'ssn'>
ssn := assn
]
ssn [
<category: 'accessing'>
^ ssn.
]
asByteArray [
"Most simple address storing routine"
| ai data |
<category: 'encoding'>
data := OrderedCollection new.
"Create the Address Information"
ai := 0.
"SSN indicator"
ai := ai bitOr: 2.
self routedOnSSN ifTrue: [
ai := ai bitOr: 64.
].
"Point Code"
poi ifNotNil: [
ai := ai bitOr: 1.
].
"GTI Indicator"
gti_ind ifNotNil: [
ai := ai bitOr: (gti_ind bitShift: 2).
].
data add: ai.
"POC"
poi ifNotNil: [
data add: ((poi bitAnd: 16r00FF) bitShift: 0).
data add: ((poi bitAnd: 16rFF00) bitShift: -8).
].
"SSN"
data add: ssn.
"GTI"
gti_ind ifNotNil: [
gti do: [:each | data add: each ].
].
data addFirst: data size.
^ data asByteArray
]
]