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/SCCPGlobalTitle.st

123 lines
4.6 KiB
Smalltalk

"
(C) 2010-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: SCCPGlobalTitle [
| indicator nai data |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the Global Title of Q.713.'>
SCCPGlobalTitle class >> gtiIndNoGTI [ <category: 'gti'> ^ 0 ]
SCCPGlobalTitle class >> gtiIndGTI [ <category: 'gti'> ^ 1 ]
SCCPGlobalTitle class >> gtiIndTransOnlyGTI [ <category: 'gti'> ^ 2 ]
SCCPGlobalTitle class >> gtiIndTransNumbrPlanAndEnc [ <category: 'gti'> ^ 3 ]
SCCPGlobalTitle class >> gtiIndTransNumbrAndMore [ <category: 'gti'> ^ 4 ]
SCCPGlobalTitle class >> naiUnknown [ <category: 'nai'> ^ 0 ]
SCCPGlobalTitle class >> naiSubscriber [ <category: 'nai'> ^ 1 ]
SCCPGlobalTitle class >> naiReservedNational [ <category: 'nai'> ^ 2 ]
SCCPGlobalTitle class >> naiNationalSign [ <category: 'nai'> ^ 3 ]
SCCPGlobalTitle class >> naiInternationalNumber [ <category: 'nai'> ^ 4 ]
SCCPGlobalTitle class >> npUnknown [ <category: 'numbering-plan'> ^ 0 ]
SCCPGlobalTitle class >> npISDN [ <category: 'numbering-plan'> ^ 1 ]
SCCPGlobalTitle class >> npGeneric [ <category: 'numbering-plan'> ^ 2 ]
SCCPGlobalTitle class >> npData [ <category: 'numbering-plan'> ^ 3 ]
SCCPGlobalTitle class >> npTelex [ <category: 'numbering-plan'> ^ 4 ]
SCCPGlobalTitle class >> npMaritime [ <category: 'numbering-plan'> ^ 5 ]
SCCPGlobalTitle class >> npLand [ <category: 'numbering-plan'> ^ 6 ]
SCCPGlobalTitle class >> npMobile [ <category: 'numbering-plan'> ^ 7 ]
SCCPGlobalTitle class >> esUnknown [ <category: 'encoding-scheme'> ^ 0 ]
SCCPGlobalTitle class >> esBCDOdd [ <category: 'encoding-scheme'> ^ 1 ]
SCCPGlobalTitle class >> esBCDEven [ <category: 'encoding-scheme'> ^ 2 ]
SCCPGlobalTitle class >> esNational [ <category: 'encoding-scheme'> ^ 3 ]
SCCPGlobalTitle class >> initWith: gti_ind data: gti [
<category: 'creation'>
self allSubclassesDo: [:each |
each subType = gti_ind
ifTrue: [
^ each initWith: gti.
].
].
^ self error: ('Unhandled gti indicator: <1p>' expandMacrosWith: gti_ind).
]
SCCPGlobalTitle class >> map: aDigit [
<category: 'creation'>
^ (aDigit >= 0 and: [aDigit <= 9])
ifTrue: [ (aDigit + 48) asCharacter ]
ifFalse: [ $N ]
]
SCCPGlobalTitle class >> unmap: aChar [
| digit |
<category: 'parsing'>
digit := aChar asInteger.
^ (digit >= 48 and: [digit <= 57])
ifTrue: [ digit - 48 ]
ifFalse: [ 16rF ].
]
SCCPGlobalTitle class >> parseAddr: data encoding: aEnc [
| odd split |
<category: 'parsing'>
(aEnc = 1 or: [aEnc = 2]) ifFalse: [
^ self error: 'Only BCD number encoding supported.'
].
split := OrderedCollection new.
data do: [:each |
split add: (self map: (each bitAnd: 16r0F)).
split add: (self map: ((each bitAnd: 16rF0) bitShift: -4)).
].
"Handle the odd case"
aEnc = 1 ifTrue: [
split removeLast.
].
^ String withAll: split.
]
SCCPGlobalTitle class >> formatAddr: aNumber on: data [
| nr odd |
<category: 'creation'>
nr := OrderedCollection new.
odd := aNumber size odd.
aNumber do: [:each |
nr add: (self unmap: each)
].
odd ifTrue: [
nr add: 16r0.
].
1 to: nr size by: 2 do: [:each|
| low high |
low := nr at: each.
high := nr at: each + 1.
data add: (low bitOr: (high bitShift: 4)).
].
]
]