aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2013-04-30 18:39:13 +0200
committerHolger Hans Peter Freyther <zecke@selfish.org>2013-04-30 18:39:13 +0200
commit4f0b583d1c1c582e9b6e2734d186c26e1c99586f (patch)
tree525684827d18b14794d2adb563a65fce951bc1ba
parent099d03f1cd0cdd5fa8031efb482cd44e07e8028a (diff)
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.
-rw-r--r--Makefile4
-rw-r--r--package.xml2
-rw-r--r--sccp/SCCP.st201
-rw-r--r--sccp/SCCPGlobalTitle.st122
-rw-r--r--sccp/SCCPGlobalTitleTranslation.st113
5 files changed, 240 insertions, 202 deletions
diff --git a/Makefile b/Makefile
index 1d4a96d..7f53907 100644
--- a/Makefile
+++ b/Makefile
@@ -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 \
diff --git a/package.xml b/package.xml
index 85946a4..0c4c41d 100644
--- a/package.xml
+++ b/package.xml
@@ -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>
diff --git a/sccp/SCCP.st b/sccp/SCCP.st
index 43026a3..9f16a98 100644
--- a/sccp/SCCP.st
+++ b/sccp/SCCP.st
@@ -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'>
diff --git a/sccp/SCCPGlobalTitle.st b/sccp/SCCPGlobalTitle.st
new file mode 100644
index 0000000..9ee871f
--- /dev/null
+++ b/sccp/SCCPGlobalTitle.st
@@ -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)).
+ ].
+ ]
+]
diff --git a/sccp/SCCPGlobalTitleTranslation.st b/sccp/SCCPGlobalTitleTranslation.st
new file mode 100644
index 0000000..c41f442
--- /dev/null
+++ b/sccp/SCCPGlobalTitleTranslation.st
@@ -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
+ ]
+]