1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-network/sccp/SCCPAddress.st

254 lines
6.7 KiB
Smalltalk

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