smalltalk
/
osmo-st-gsm
Archived
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-gsm/GSM411.st

373 lines
12 KiB
Smalltalk

"
(C) 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/>.
"
"Message for GSM04.11"
GSM48DataHolder subclass: GSM411CpUserData [
<category: 'OsmoGSM-SMS-Types'>
<comment: '8.1.4.1'>
<gsmElementId: 2r01>
<gsmMinValueSize: 0 max: 248>
<gsmName: 'userData'>
]
GSM48SimpleTag subclass: GSM411CpCause [
<category: 'OsmoGSM-SMS-Types'>
<comment: '8.1.4.2'>
<gsmElementId: 2r10>
<gsmName: 'cause'>
GSM411CpCause class [
causeNetworkFailure [ <category: 'cause'> ^ 17 ]
causeCongestion [ <category: 'cause'> ^ 22 ]
causeInvalidTransaction [ <category: 'cause'> ^ 81 ]
causeSemanticallyIncorrectMessage [ <category: 'cause'> ^ 95 ]
causeInvalidatMandatoryInformation [ <category: 'cause'> ^ 96 ]
causeMessageTypeNonExistent [ <category: 'cause'> ^ 97 ]
causeMessageNotCompatible [ <category: 'cause'> ^ 98 ]
causeInformationElementNonExistent [ <category: 'cause'> ^ 99 ]
causeProtocolError [ <category: 'cause'> ^ 111 ]
]
]
GSM48SimpleTag subclass: GSM411RpMessageType [
<category: 'OsmoGSM-SMS-Types'>
<comment: '8.2.2'>
]
GSM48FixedSizeIE subclass: GSM411RpMessageReference [
<category: 'OsmoGSM-SMS-Types'>
<comment: '8.2.3'>
<gsmValueLength: 1>
]
GSM48DataHolder subclass: GSM411RpOriginatorAddress [
<category: 'OsmoGSM-SMS-Types'>
<comment: '8.2.5.1'>
<gsmMinValueSize: 0 max: 11>
]
GSM48DataHolder subclass: GSM411RpDestinationAddress [
<category: 'OsmoGSM-SMS-Types'>
<comment: '8.2.5.2'>
<gsmMinValueSize: 0 max: 11>
]
GSM48DataHolder subclass: GSM411RpUserData [
<category: 'OsmoGSM-SMS-Types'>
<comment: '8.2.5.3'>
<gsmElementId: 2r1000001>
<gsmMinValueSize: 0 max: 233>
]
GSM48DataHolder subclass: GSM411RpCause [
<category: 'OsmoGSM-SMS-Types'>
<comment: '8.2.5.4'>
<gsmElementId: 2r1000010>
<gsmMinValueSize: 1 max: 2>
GSM411RpCause class [
"MO Causes"
causeUnassignedNumber [ <category: 'cause'> ^ 1 ]
causeOperatorDeterminedBar [ <category: 'cause-mo'> ^ 8 ]
causeCallBarred [ <category: 'cause-mo'> ^ 10 ]
causeReserved [ <category: 'cause-mo'> ^ 11 ]
causeShortMessageTransferRejected [ <category: 'cause-mo'> ^ 21 ]
causeDestinationOutOfOrder [ <category: 'cause-mo'> ^ 27 ]
causeUnidentifiedSubscriber [ <category: 'cause-mo'> ^ 28 ]
causeFacilityRejected [ <category: 'cause-mo'> ^ 29 ]
causeUnknownSubscriber [ <category: 'cause-mo'> ^ 30 ]
causeNetworkOutOfOrder [ <category: 'cause-mo'> ^ 38 ]
causeTemporaryFailure [ <category: 'cause-mo'> ^ 41 ]
causeCongestion [ <category: 'cause-mo'> ^ 42 ]
causeResourcesUnavilable [ <category: 'cause-mo'> ^ 47 ]
causeRequestedFacilityNotSubscribed [ <category: 'cause-mo'> ^ 50 ]
causeRequestedFacilityNotImplemented [ <category: 'cause-mo'> ^ 69 ]
causeInterworkingUnspecified [ <category: 'cause-mo'> ^ 127 ]
"MT causes"
causeMemoryCapacityExceeded [ <category: 'cause-mt'> ^ 22 ]
"Common code"
causeInvalidShortMessageTransferReference [ <category: 'cause'> ^ 81 ]
causeSemanticallyIncorrectMessage [ <category: 'cause'> ^ 95 ]
causeInvalidatMandatoryInformation [ <category: 'cause'> ^ 96 ]
causeMessageTypeNonExistent [ <category: 'cause'> ^ 97 ]
causeMessageNotCompatible [ <category: 'cause'> ^ 98 ]
causeInformationElementNonExistent [ <category: 'cause'> ^ 99 ]
causeProtocolError [ <category: 'cause'> ^ 111 ]
memoryAvailableMessages [
"Cause names and type for memory available notification"
^ OrderedCollection new
add: #causeUnknownSubscriber -> #Permanent;
add: #causeNetworkOutOfOrder -> #Temporary;
add: #causeTemporaryFailure -> #Temporary;
add: #causeCongestion -> #Temporary;
add: #causeResourcesUnavilable -> #Temporary;
add: #causeRequestedFacilityNotImplemented -> #Permanent;
add: #causeSemanticallyIncorrectMessage -> #Permanent;
add: #causeInvalidatMandatoryInformation -> #Permanent;
add: #causeMessageTypeNonExistent -> #Permanent;
add: #causeMessageNotCompatible -> #Permanent;
add: #causeInformationElementNonExistent -> #Permanent;
add: #causeProtocolError -> #Permanent;
add: #causeInterworkingUnspecified -> #Permanent;
yourself
]
]
]
GSM48MSG subclass: GSMCpMessage [
<category: 'OsmoGSM-SMS-Message'>
GSMCpMessage class >> msgCpData [ <category: 'type'> ^ 2r00000001 ]
GSMCpMessage class >> msgCpAck [ <category: 'type'> ^ 2r00000100 ]
GSMCpMessage class >> msgCpError[ <category: 'type'> ^ 2r00010000 ]
GSMCpMessage class >> isGSMBaseclass [ <category: 'gsm'> ^ self = GSMCpMessage ]
GSMCpMessage class >> classType [ <category: 'gsm'> ^ 16r9 ]
ti [
^ ti ifNil: [ 0 ]
]
]
GSMCpMessage subclass: GSMCpData [
<category: 'OsmoGSM-SMS-Message'>
<comment: '7.2.1'>
GSMCpData class >> messageType [ <category: 'gsm'> ^ self msgCpData ]
GSMCpData class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: GSM411CpUserData asTLVDescription;
yourself
]
rpMessage [
^GSMRpMessage decode: self userData data readStream.
]
]
GSMCpMessage subclass: GSMCpAck [
<category: 'OsmoGSM-SMS-Message'>
<comment: '7.2.2'>
GSMCpAck class >> messageType [ <category: 'gsm'> ^ self msgCpAck ]
GSMCpAck class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
]
]
GSMCpMessage subclass: GSMCpError [
<category: 'OsmoGSM-SMS-Message'>
<comment: '7.2.3'>
GSMCpError class >> messageType [ <category: 'gsm'> ^ self msgCpError ]
GSMCpError class >> tlvDescription [
<category: 'parsing'>
^ OrderedCollection new
add: GSM411CpCause asTLVDescription;
yourself
]
]
Object subclass: GSMRpInformationElement [
<category: 'OsmoGSM-SMS-Message'>
GSMRpInformationElement class >> readFrom: aStream with: anAttr [
| len |
len := aStream next asInteger.
len printNl.
^self new
readFrom: (aStream next: len);
yourself.
]
]
GSMRpInformationElement subclass: GSMRpOrigantorAddress [
| data |
<category: 'OsmoGSM-SMS-Message'>
GSMRpOrigantorAddress class >> asTLVDescription [
^Osmo.TLVDescription new
beLV; instVarName: #origAddress; parseClass: self;
yourself.
]
readFrom: anArray [
data := anArray
]
writeOn: aMessage with: anAttribute [
aMessage
putByte: data size;
putByteArray: data
]
]
GSMRpInformationElement subclass: GSMRpDestinationAddress [
| data |
<category: 'OsmoGSM-SMS-Message'>
GSMRpDestinationAddress class >> asTLVDescription [
^Osmo.TLVDescription new
beLV; instVarName: #destAddress; parseClass: self;
yourself.
]
readFrom: anArray [
data := anArray
]
writeOn: aMessage with: anAttribute [
aMessage
putByte: data size;
putByteArray: data
]
]
GSMRpInformationElement subclass: GSMRpUserData [
| data |
<category: 'OsmoGSM-SMS-Message'>
GSMRpUserData class >> asTLVDescription [
^Osmo.TLVDescription new
beTLV; instVarName: #userData; parseClass: self;
tag: 16r41; yourself.
]
readFrom: anArray [
data := anArray
]
writeOn: aMessage with: anAttribute [
aMessage
putByte: data size;
putByteArray: data
]
]
Osmo.TLVParserBase subclass: GSMRpMessage [
| direction reference |
<category: 'OsmoGSM-SMS-Message'>
GSMRpMessage class >> decode: aStream [
<category: '8.2.2'>
| mti |
"GSM 04.11 has a crazy table in 8.2.2 for the Message type indicator.
The decoding depends on the direction but right now it is still unique
so we can determine direction and and message type from that number."
mti := (aStream next bitAnd: 2r111).
mti = 2r000 ifTrue: [^GSMRpData new decode: aStream direction: #msn].
mti = 2r001 ifTrue: [^GSMRpData new decode: aStream direction: #nms].
mti = 2r010 ifTrue: [^GSMRpAck new decode: aStream direction: #msn].
mti = 2r011 ifTrue: [^GSMRpAck new decode: aStream direction: #nms].
mti = 2r100 ifTrue: [^GSMRpError new decode: aStream direction: #msn].
mti = 2r101 ifTrue: [^GSMRpError new decode: aStream direction: #nms].
mti = 2r110 ifTrue: [^GSMRpSmma new decode: aStream direction: #msn].
^self error: 'Can not decode ', mti displayString.
]
decode: aStream direction: aDirection [
direction := aDirection.
reference := aStream next asInteger.
self class tlvDescription do: [:attr |
attr isMandatory ifTrue:
[self doParse: attr stream: aStream].
attr isOptional ifTrue:
[self parseOptional: attr tag: aStream peek stream: aStream].
].
]
writeHeaderOn: aMessage [
direction = #msn
ifTrue: [aMessage putByte: self class messageTypeToNetwork]
ifFalse: [aMessage putByte: self class messageTypeToMS].
aMessage putByte: reference.
]
]
GSMRpMessage subclass: GSMRpData [
| origAddress destAddress userData |
<category: 'OsmoGSM-SMS-Message'>
<comment: '7.3.1'>
GSMRpData class >> messageTypeToNetwork [
^2r000
]
GSMRpData class >> messageTypeToMS [
^2r001
]
GSMRpData class >> tlvDescription [
^OrderedCollection new
add: GSMRpOrigantorAddress asTLVDescription;
add: GSMRpDestinationAddress asTLVDescription;
add: GSMRpUserData asTLVDescription;
yourself.
]
]
GSMRpMessage subclass: GSMRpSmma [
<category: 'OsmoGSM-SMS-Message'>
<comment: '7.3.2'>
GSMRpSmma class >> tlvDescription [
^OrderedCollection new
]
]
GSMRpMessage subclass: GSMRpAck [
| userData |
<category: 'OsmoGSM-SMS-Message'>
<comment: '7.3.3'>
GSMRpAck class >> tlvDescription [
^OrderedCollection new
add: GSMRpUserData asTLVDescription beOptional yourself;
yourself.
]
GSMRpAck class >> messageTypeToNetwork [
^2r010
]
]
GSMRpMessage subclass: GSMRpError [
| cause userData |
<category: 'OsmoGSM-SMS-Message'>
<comment: '7.3.4'>
GSMRpError class >> tlvDescription [
^OrderedCollection new
add: GSMRpCause asTLVDescription;
add: GSMRpUserData asTLVDescription beOptional;
yourself
]
]
Eval [
GSMCpData initialize.
GSMCpAck initialize.
GSMCpError initialize.
]