aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2013-04-30 18:35:35 +0200
committerHolger Hans Peter Freyther <zecke@selfish.org>2013-04-30 18:35:35 +0200
commit099d03f1cd0cdd5fa8031efb482cd44e07e8028a (patch)
tree5fdcaef3480796d00810478c7d8e5280718ef2b9
parente46ebff2379e5af4b3d1b1a9931ed57dd8f97602 (diff)
sccp: Rename SCCPGTI to SCCPGlobalTitle
Rename it to SCCPGlobalTitle and drop the "indicator" as it is not an indicator at all.
-rw-r--r--Tests.st4
-rw-r--r--sccp/SCCP.st72
-rw-r--r--sccp/SCCPAddress.st2
3 files changed, 39 insertions, 39 deletions
diff --git a/Tests.st b/Tests.st
index 443fbee..5ece3e9 100644
--- a/Tests.st
+++ b/Tests.st
@@ -197,8 +197,8 @@ TestCase subclass: SCCPTests [
"Now test the GTI parsing"
gti := parsed gtiAsParsed.
self assert: gti translation = 0.
- self assert: gti plan = SCCPGTI npISDN.
- self assert: gti nature = SCCPGTI naiInternationalNumber.
+ self assert: gti plan = SCCPGlobalTitle npISDN.
+ self assert: gti nature = SCCPGlobalTitle naiInternationalNumber.
self assert: gti addr = '3548900073'.
parsed gtiFromAddr: gti.
self assert: parsed asByteArray = addr.
diff --git a/sccp/SCCP.st b/sccp/SCCP.st
index 2466078..43026a3 100644
--- a/sccp/SCCP.st
+++ b/sccp/SCCP.st
@@ -135,39 +135,39 @@ Object subclass: SCCPPNC [
]
]
-Object subclass: SCCPGTI [
+Object subclass: SCCPGlobalTitle [
| indicator nai data |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the Global Title of Q.713.'>
- SCCPGTI class >> gtiIndNoGTI [ <category: 'gti'> ^ 0 ]
- SCCPGTI class >> gtiIndGTI [ <category: 'gti'> ^ 1 ]
- SCCPGTI class >> gtiIndTransOnlyGTI [ <category: 'gti'> ^ 2 ]
- SCCPGTI class >> gtiIndTransNumbrPlanAndEnc [ <category: 'gti'> ^ 3 ]
- SCCPGTI class >> gtiIndTransNumbrAndMore [ <category: 'gti'> ^ 4 ]
-
- SCCPGTI class >> naiUnknown [ <category: 'nai'> ^ 0 ]
- SCCPGTI class >> naiSubscriber [ <category: 'nai'> ^ 1 ]
- SCCPGTI class >> naiReservedNational [ <category: 'nai'> ^ 2 ]
- SCCPGTI class >> naiNationalSign [ <category: 'nai'> ^ 3 ]
- SCCPGTI class >> naiInternationalNumber [ <category: 'nai'> ^ 4 ]
-
- SCCPGTI class >> npUnknown [ <category: 'numbering-plan'> ^ 0 ]
- SCCPGTI class >> npISDN [ <category: 'numbering-plan'> ^ 1 ]
- SCCPGTI class >> npGeneric [ <category: 'numbering-plan'> ^ 2 ]
- SCCPGTI class >> npData [ <category: 'numbering-plan'> ^ 3 ]
- SCCPGTI class >> npTelex [ <category: 'numbering-plan'> ^ 4 ]
- SCCPGTI class >> npMaritime [ <category: 'numbering-plan'> ^ 5 ]
- SCCPGTI class >> npLand [ <category: 'numbering-plan'> ^ 6 ]
- SCCPGTI class >> npMobile [ <category: 'numbering-plan'> ^ 7 ]
-
- SCCPGTI class >> esUnknown [ <category: 'encoding-scheme'> ^ 0 ]
- SCCPGTI class >> esBCDOdd [ <category: 'encoding-scheme'> ^ 1 ]
- SCCPGTI class >> esBCDEven [ <category: 'encoding-scheme'> ^ 2 ]
- SCCPGTI class >> esNational [ <category: 'encoding-scheme'> ^ 3 ]
-
- SCCPGTI class >> initWith: gti_ind data: gti [
+ 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 |
@@ -180,14 +180,14 @@ Object subclass: SCCPGTI [
^ self error: ('Unhandled gti indicator: <1p>' expandMacrosWith: gti_ind).
]
- SCCPGTI class >> map: aDigit [
+ SCCPGlobalTitle class >> map: aDigit [
<category: 'creation'>
^ (aDigit >= 0 and: [aDigit <= 9])
ifTrue: [ (aDigit + 48) asCharacter ]
ifFalse: [ $N ]
]
- SCCPGTI class >> unmap: aChar [
+ SCCPGlobalTitle class >> unmap: aChar [
| digit |
<category: 'parsing'>
digit := aChar asInteger.
@@ -196,7 +196,7 @@ Object subclass: SCCPGTI [
ifFalse: [ 16rF ].
]
- SCCPGTI class >> parseAddr: data encoding: aEnc [
+ SCCPGlobalTitle class >> parseAddr: data encoding: aEnc [
| odd split |
<category: 'parsing'>
(aEnc = 1 or: [aEnc = 2]) ifFalse: [
@@ -217,7 +217,7 @@ Object subclass: SCCPGTI [
^ String withAll: split.
]
- SCCPGTI class >> formatAddr: aNumber on: data [
+ SCCPGlobalTitle class >> formatAddr: aNumber on: data [
| nr odd |
<category: 'creation'>
@@ -240,15 +240,15 @@ Object subclass: SCCPGTI [
]
]
-SCCPGTI subclass: SCCPGTITranslation [
+SCCPGlobalTitle subclass: SCCPGlobalTitleTranslation [
| trans plan enc nature addr |
<category: 'OsmoNetwork-SCCP'>
<comment: 'I represent the global title translation specific
encoing of a SCCP header.'>
- SCCPGTITranslation class >> subType [ <category: 'constants'> ^ 4 ]
- SCCPGTITranslation class >> initWith: data [
+ SCCPGlobalTitleTranslation class >> subType [ <category: 'constants'> ^ 4 ]
+ SCCPGlobalTitleTranslation class >> initWith: data [
| enc |
<category: 'creation'>
@@ -330,7 +330,7 @@ SCCPGTI subclass: SCCPGTITranslation [
data add: nature.
"encode the number"
- SCCPGTI formatAddr: addr on: data.
+ SCCPGlobalTitle formatAddr: addr on: data.
^ data asByteArray
]
diff --git a/sccp/SCCPAddress.st b/sccp/SCCPAddress.st
index de9909b..5c1c809 100644
--- a/sccp/SCCPAddress.st
+++ b/sccp/SCCPAddress.st
@@ -136,7 +136,7 @@ Object subclass: SCCPAddress [
<category: 'gti'>
^ gti_ind = 0
ifTrue: [nil]
- ifFalse: [SCCPGTI initWith: gti_ind data: globalTitle].
+ ifFalse: [SCCPGlobalTitle initWith: gti_ind data: globalTitle].
]
gtiFromAddr: aGlobalTitle [