1
0
Fork 0

sccp: Move the SCCPGlobalTitle and SCCPGlobalTitleTranslation to new files

Split out the SCCPGlobalTitle and SCCPGlobalTitleTranslation to new
files and update the Makefile and package.xml for the new file.
This commit is contained in:
Holger Hans Peter Freyther 2013-04-30 18:39:13 +02:00
parent 099d03f1cd
commit 4f0b583d1c
5 changed files with 240 additions and 202 deletions

View File

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

View File

@ -24,6 +24,8 @@
<filein>ipa/IPAMsg.st</filein>
<filein>sccp/SCCP.st</filein>
<filein>sccp/SCCPAddress.st</filein>
<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>

View File

@ -135,207 +135,6 @@ Object subclass: SCCPPNC [
]
]
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: 16rF.
].
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)).
].
]
]
SCCPGlobalTitle subclass: SCCPGlobalTitleTranslation [
| trans plan enc nature addr |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the global title translation specific
encoing of a SCCP header.'>
SCCPGlobalTitleTranslation class >> subType [ <category: 'constants'> ^ 4 ]
SCCPGlobalTitleTranslation class >> initWith: data [
| enc |
<category: 'creation'>
enc := (data at: 2) bitAnd: 16r0F.
^ self new
translation: (data at: 1);
plan: (((data at: 2) bitAnd: 16rF0) bitShift: -4);
encoding: enc;
nature: ((data at: 3) bitAnd: 16r7F);
addr: (self parseAddr: (data copyFrom: 4) encoding: enc);
yourself
]
translation [
<category: 'accessing'>
^ trans ifNil: [ 0 ]
]
translation: aTrans [
<category: 'accessing'>
trans := aTrans
]
plan [
<category: 'accessing'>
^ plan
]
plan: aPlan [
<category: 'accessing'>
plan := aPlan
]
encoding [
<category: 'accessing'>
^ enc ifNil: [
addr size odd
ifTrue: [
1
]
ifFalse: [
2
].
].
]
encoding: aEnc [
<category: 'accessing'>
enc := aEnc
]
nature [
<category: 'accessing'>
^ nature
]
nature: aNai [
<category: 'accessing'>
nature := aNai
]
addr [
<category: 'accessing'>
^ addr
]
addr: anAddr [
<category: 'accessing'>
addr := anAddr
]
asByteArray [
| data |
<category: 'encoding'>
data := OrderedCollection new.
"write the header"
data add: self translation.
data add: ((plan bitShift: 4) bitOr: self encoding).
data add: nature.
"encode the number"
SCCPGlobalTitle formatAddr: addr on: data.
^ data asByteArray
]
]
Object subclass: SCCPAddrReference [
<category: 'OsmoNetwork-SCCP'>

122
sccp/SCCPGlobalTitle.st Normal file
View File

@ -0,0 +1,122 @@
"
(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: 16rF.
].
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)).
].
]
]

View File

@ -0,0 +1,113 @@
"
(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/>.
"
SCCPGlobalTitle subclass: SCCPGlobalTitleTranslation [
| trans plan enc nature addr |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the global title translation specific
encoing of a SCCP header.'>
SCCPGlobalTitleTranslation class >> subType [ <category: 'constants'> ^ 4 ]
SCCPGlobalTitleTranslation class >> initWith: data [
| enc |
<category: 'creation'>
enc := (data at: 2) bitAnd: 16r0F.
^ self new
translation: (data at: 1);
plan: (((data at: 2) bitAnd: 16rF0) bitShift: -4);
encoding: enc;
nature: ((data at: 3) bitAnd: 16r7F);
addr: (self parseAddr: (data copyFrom: 4) encoding: enc);
yourself
]
translation [
<category: 'accessing'>
^ trans ifNil: [ 0 ]
]
translation: aTrans [
<category: 'accessing'>
trans := aTrans
]
plan [
<category: 'accessing'>
^ plan
]
plan: aPlan [
<category: 'accessing'>
plan := aPlan
]
encoding [
<category: 'accessing'>
^ enc ifNil: [
addr size odd
ifTrue: [
1
]
ifFalse: [
2
].
].
]
encoding: aEnc [
<category: 'accessing'>
enc := aEnc
]
nature [
<category: 'accessing'>
^ nature
]
nature: aNai [
<category: 'accessing'>
nature := aNai
]
addr [
<category: 'accessing'>
^ addr
]
addr: anAddr [
<category: 'accessing'>
addr := anAddr
]
asByteArray [
| data |
<category: 'encoding'>
data := OrderedCollection new.
"write the header"
data add: self translation.
data add: ((plan bitShift: 4) bitOr: self encoding).
data add: nature.
"encode the number"
SCCPGlobalTitle formatAddr: addr on: data.
^ data asByteArray
]
]