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

108 lines
2.6 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/>.
"
SCCPGlobalTitle subclass: SCCPGlobalTitleTranslation [
| trans plan 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);
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'>
^addr size odd
ifTrue: [1]
ifFalse: [2]
]
nature [
<category: 'accessing'>
^ nature
]
nature: aNai [
<category: 'accessing'>
nature := aNai
]
address [
<category: 'accessing'>
^addr
]
addr [
<category: 'accessing'>
^self address
]
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
]
]