" (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 . " "Messages for GSM04.08" """ IEs for GSM48MSG """ IEBase subclass: GSM48IE [ GSM48IE class [ | gsmName gsmElementId gsmIeMask | gsmName: aName [ gsmName := aName asSymbol ] gsmElementId: anId [ gsmElementId := anId ] gsmIeMask: aMask [ gsmIeMask := aMask ] ieMask [ "Some IEs encode the IE and the value into one. Return the mask to be used to determine the IE and see if it is matching." ^ gsmIeMask ifNil: [16rFF] ] gsmName [ ^gsmName ] gsmElementId [ ^gsmElementId ] gsmIeMask [ ^gsmIeMask ] classPragmas [ ^super classPragmas, #(#gsmName #gsmElementId #gsmIeMask) ] ] GSM48IE class >> elementId [ ^ gsmElementId ] GSM48IE class >> asTLVDescription [ ^ Osmo.TLVDescription new tag: gsmElementId; parseClass: self; instVarName: gsmName; yourself ] ] GSM48IE subclass: GSM48FixedSizeIE [ GSM48FixedSizeIE class [ | gsmValueLength | gsmValueLength: aLength [ gsmValueLength := aLength ] classPragmas [ ^super classPragmas, #(#gsmValueLength) ] length: aStream [ ^ self gsmValueLength ] length [ "TODO: deprecate and remove" ^ self gsmValueLength ] gsmValueLength [ ^ gsmValueLength ifNil: [ self = GSM48FixedSizeIE ifTrue: [nil] ifFalse: [self superclass gsmValueLength]] ] asTLVDescription [ ^ super asTLVDescription beTV; valueSize: gsmValueLength; yourself ] ] ] GSM48IE subclass: GSM48VariableSizedIE [ GSM48VariableSizedIE class [ | gsmValueRange | length: aStream [ ^ aStream peek + 1 ] asTLVDescription [ ^ super asTLVDescription minSize: self validSizes first maxSize: self validSizes last; beTLV; yourself ] gsmMinValueSize: aMin max: aMax [ gsmValueRange := aMin to: aMax. ] gsmValueSizeMin [ ^(self = GSM48VariableSizedIE or: [self = GSM48DataHolder]) ifTrue: [nil] ifFalse: [gsmValueRange first] ] gsmValueSizeMax [ ^(self = GSM48VariableSizedIE or: [self = GSM48DataHolder]) ifTrue: [nil] ifFalse: [gsmValueRange last] ] gsmValueSizeMin: aMin [ | last | last := gsmValueRange isNil ifTrue: [aMin] ifFalse: [gsmValueRange last]. gsmValueRange := aMin to: last. ] gsmValueSizeMax: aMax [ | first | first := gsmValueRange isNil ifTrue: [aMax] ifFalse: [gsmValueRange first]. gsmValueRange := first to: aMax. ] classPragmas [ "The gsmMinValueSize:max: can not be expressed right now." ^super classPragmas, #(#gsmValueSizeMin #gsmValueSizeMax). ] validSizes [ "Default size" ^ gsmValueRange ifNil: [1 to: 180]. ] ] ] GSM48FixedSizeIE subclass: GSM48SimpleTag [ | value | GSM48SimpleTag class >> initWithData: aData [ ^ self new value: aData; yourself ] GSM48SimpleTag class >> asTLVDescription [ ^ super asTLVDescription beTagOnly; valueSize: 0; yourself ] value: aValue [ | inv | inv := 255 - self class ieMask. value := (aValue bitAnd: inv) ] value [ ^ value ifNil: [ 0 ] ] writeOn: aMsg [ | combined | combined := self class elementId bitOr: value. aMsg putByte: combined. ] writeOnDirect: aMsg [ self shouldNotImplement ] ] GSM48VariableSizedIE subclass: GSM48DataHolder [ | data | GSM48DataHolder class >> createDefault [ | size data | size := self validSizes first. data := ByteArray new: size. ^ self new data: data; yourself. ] GSM48DataHolder class >> initWithData: aData [ ^ self new data: aData; yourself. ] GSM48DataHolder class >> parseFrom: aStream [ | len | len := aStream next. ^ self initWithData: (aStream next: len) ] data: aData [ | size | "Add the size for the length header" (self class validSizes includes: aData size) ifFalse: [ ^ self error: 'The data is not of a valid size: %1 "%2"' % {aData size. self class validSizes}. ]. data := aData. ] data [ ^ data ] writeOn: aMsg [ aMsg putByte: self class elementId. aMsg putByte: data size. aMsg putByteArray: data. ] writeOnDirect: aMsg [ aMsg putByte: data size. aMsg putByteArray: data. ] ] GSM48FixedSizeIE subclass: GSM48SimpleData [ | data | GSM48SimpleData class >> initWithData: aData [ ^ self new data: aData; yourself. ] GSM48SimpleData class >> defaultValue [ ^ ByteArray new: self length ] GSM48SimpleData class >> createDefault [ ^ self new data: self defaultValue; yourself ] GSM48SimpleData class >> parseFrom: aStream [ | dat | dat := aStream next: self length. ^ self new data: dat; yourself ] data [ ^ data ] data: aData [ aData size = self class length ifFalse: [ Error signal: 'DATA needs to be ', self class length asString, ' long.', 'But it was ', aData size asString, ' long.'. ]. data := aData. ] writeOnDirect: aMsg [ aMsg putByteArray: data. ] writeOn: aMsg [ "Write a TV" aMsg putByte: self class elementId. self writeOnDirect: aMsg ] ] GSM48SimpleData subclass: GSM48PageAndDedicatedMode [ ] GSM48SimpleData subclass: GSM48CellDescription [ ncc [ ^ (data first bitShift: -3) bitAnd: 2r111 ] bcc [ ^ (data first bitShift: -0) bitAnd: 2r111 ] bcch [ | hi low | hi := data first bitShift: -6. low := data second. ^ (hi bitShift: 8) bitOr: low. ] ] GSM48SimpleData subclass: GSM48ChannelDescription [ timeslotNumber [ ^ (data at: 1) bitAnd: 2r111 ] channelType [ ^ (data at: 1) bitShift: -3 ] ] GSM48SimpleData subclass: GSM48ChannelDescription2 [ channelType [ ^ data first bitShift: -3. ] timeSlot [ ^ data first bitAnd: 2r111 ] isH1 [ ^ (data second bitAt: 5) = 1 ] isH0 [ ^ (data second bitAt: 5) = 0 ] arfcn [ | low | self isH0 ifFalse: [^self error: 'ARFCN requires H=0']. low := data second bitAnd: 2r11. ^ (low bitShift: 8) bitOr: data third. ] ] GSM48SimpleData subclass: GSM48ChannelMode [ | mode | GSM48ChannelMode class [ modeSignallingOnly [ ^ 2r00000000 ] modeSpeechVersion1 [ ^ 2r00000001 ] modeSpeechVersion2 [ ^ 2r00100001 ] modeSpeechVersion3 [ ^ 2r01000001 ] modeData145 [ ^ 2r00001111 ] modeData120 [ ^ 2r00000011 ] modeData60 [ ^ 2r00001011 ] modeData36 [ ^ 2r00010011 ] ] GSM48ChannelMode class >> defaultValue [ ^ ByteArray with: self modeSignallingOnly ] mode [ ^ data first ] mode: aMode [ data := ByteArray with: aMode. ] ] GSM48SimpleData subclass: GSM48ChannelMode2 [ | mode | ] GSM48ChannelDescription subclass: GSM48ChannelOrPacketDescription [ "broken stuff.. I really need to add a proper conditional checking here..." ] GSM48SimpleTag subclass: GSM48CipherModeSetting [ ] GSM48SimpleData subclass: GSM48CipherModeSettingResponse [ ] GSM48SimpleData subclass: GSM48FrequencyChannelSequence [ ] GSM48DataHolder subclass: GSM48FrequencyList [ ] GSM48SimpleData subclass: GSM48FrequencyShortList [ ] GSM48SimpleData subclass: GSM48HandoverReference [ value [ ^ data first ] ] GSM48DataHolder subclass: GSM48MultislotAllocation [ ] GSM48SimpleData subclass: GSM48PowerCommandAndAccess [ ] GSM48SimpleData subclass: GSM48TimingAdvance [ ] GSM48SimpleData subclass: GSM48TimingDifference [ ] GSM48DataHolder subclass: GSM48VGCSTargetModeIndication [ ] GSM48SimpleData subclass: GSM48StartingTime [ ] GSM48SimpleTag subclass: GSM48SynchronizationInd [ ] GSM48SimpleData subclass: GSM48RequestReference [ ra [ ^ data at: 1 ] t1 [ ^ (data at: 2) bitShift: - 3 ] t2 [ ^ (data at: 3) bitAnd: 2r00011111 ] t3 [ | high low | high := (data at: 2) bitAnd: 2r111. low := (data at: 3) bitShift: -5. ^ low bitOr: (high bitShift: 3) ] ] GSM48DataHolder subclass: GSM48IARestOctets [ GSM48IARestOctets class >> length: aStream [ self shouldNotImplement ] GSM48IARestOctets class >> asTLVDescription [ ^ super asTLVDescription beTV; yourself ] GSM48IARestOctets class >> parseFrom: aStream [ "Consume the rest of the stream. There is no length for the octets" ^ self initWithData: (aStream upToEnd) ] writeOn: aMsg [ ^ self shouldNotImplement ] writeOnDirect: aMsg [ aMsg putByteArray: self data ] ] GSM48DataHolder subclass: GSM48MobileAllocation [ ] GSM48DataHolder subclass: GSM48MultiRateConfiguration [ ] GSM48SimpleData subclass: GSM48KeySeqLuType [ GSM48KeySeqLuType class >> cmTypeMOCall [ ^ 2r0001 ] GSM48KeySeqLuType class >> cmTypeEmergency [ ^ 2r0010 ] GSM48KeySeqLuType class >> cmTypeSMS [ ^ 2r0100 ] GSM48KeySeqLuType class >> cmTypeSS [ ^ 2r1000 ] GSM48KeySeqLuType class >> cmTypeVGCall [ ^ 2r1001 ] GSM48KeySeqLuType class >> cmTypeVBCall [ ^ 2r1010 ] GSM48KeySeqLuType class >> cmTypeLocation [ ^ 2r1011 ] GSM48KeySeqLuType class >> luFollowOnRequest [ ^ 2r1000 ] GSM48KeySeqLuType class >> luTypeNormal [ ^ 2r00 ] GSM48KeySeqLuType class >> luTypePeriodic [ ^ 2r01 ] GSM48KeySeqLuType class >> luTypeIMSIAttach [ ^ 2r10 ] GSM48KeySeqLuType class >> luTypeReserved [ ^ 2r11 ] GSM48KeySeqLuType class >> createDefault [ ^ (self new) val: 16r70; yourself ] luType: aVal [ | tmp | tmp := self val clearBit: 2r11. tmp := tmp bitOr: (aVal bitAnd: 2r11). self val: tmp. ] val [ ^ self data at: 1 ] val: aVal [ self data: (ByteArray with: aVal). ] ] GSM48FixedSizeIE subclass: GSM48Lai [ | lai lac | GSM48Lai class >> createDefault [ ^ (self new) lai: (LAI initWith: 0 mnc: 0); lac: 0; yourself ] GSM48Lai class >> parseFrom: aStream [ "TODO: as nextUShort to the ReadStream..." ^ (self new) lai: (LAI parseFrom: aStream); lac: ((aStream next: 2) asByteArray ushortAt: 1) swap16; yourself ] mcc: aMcc [ lai mcc: aMcc ] mnc: aMnc [ lai mnc: aMnc ] lai: aLai [ lai := aLai ] lac: aLac [ lac := aLac ] mcc [ ^ lai mcc ] mnc [ ^ lai mnc ] lac [ ^ lac ] writeOnDirect: aMsg [ lai writeOn: aMsg. aMsg putLen16: lac. ] ] GSM48FixedSizeIE subclass: GSM48Classmark1 [ | cm1 | GSM48Classmark1 class >> createDefault [ ^ (self new) cm1: 16r33; yourself ] GSM48Classmark1 class >> parseFrom: aStream [ ^ (self new) cm1: aStream next; yourself ] cm1: aCm [ cm1 := aCm ] cm1 [ ^ cm1 ] writeOnDirect: aMsg [ aMsg putByte: cm1. ] ] GSM48DataHolder subclass: GSM48Classmark2 [ "TODO: This is broken... it needs to be a simple data holder" GSM48Classmark2 class >> createDefault [ ^ self new data: self defaultValue; yourself ] GSM48Classmark2 class >> defaultValue [ ^ ByteArray with: 16r33 with: 16r19 with: 16rA2. ] ] GSM48DataHolder subclass: GSM48Classmark3 [ GSM48Classmark3 class >> createDefault [ ^ self new data: self defaultValue; yourself ] GSM48Classmark3 class >> defaultValue [ ^ #(16r60 16r14 16r4C 16r8F 16r60 16r3B 16r88 16r00 16r90) asByteArray. ] ] GSM48VariableSizedIE subclass: GSM48MIdentity [ | type id | GSM48MIdentity class >> createDefault [ ^ (self new) imsi: '000000000000'; yourself ] GSM48MIdentity class >> parseFrom: aStream [ ^ self parseFrom: aStream length: aStream next ] GSM48MIdentity class >> parseFrom: aStream length: len [ | head type id | head := aStream next. type := head bitAnd: 16r7. id := type = GSM48IdentityType typeTMSI ifTrue: [self parseTMSI: aStream length: len head: head] ifFalse: [self parseBCDId: aStream length: len head: head]. ^ self new type: type; id: id; yourself ] GSM48MIdentity class >> parseTMSI: aStream length: aLength head: aHead [ aLength = 5 ifFalse: [^self error: 'MI should be five bytes']. ^ aStream next: 4. ] GSM48MIdentity class >> parseBCDId: aStream length: aLength head: aHead [ | digits odd | digits := OrderedCollection new. odd := (aHead bitShift: -3) bitAnd: 16r1. digits add: ((aHead bitShift: -4) bitAnd: 16rF). 3 to: (1 + aLength) do: [:each | | val | val := aStream next. digits add: (val bitAnd: 16rF). digits add: ((val bitShift: -4) bitAnd: 16rF). ]. "The last was just a dummy value" odd = 1 ifFalse: [ digits removeLast. ]. ^ (BCD decode: digits) asString. ] imsi: anImsi [ type := GSM48IdentityType typeIMSI. self id: anImsi. ] imsi [ self type = GSM48IdentityType typeIMSI ifFalse: [^self error: 'Underlying type is not an IMSI']. ^ id ] imei: anImei [ type := GSM48IdentityType typeIMEI. self id: anImei. ] imei [ self type = GSM48IdentityType typeIMEI ifFalse: [^self error: 'Underlying type is not an IMEI']. ^ id ] tmsi: aTmsi [ aTmsi size = 4 ifFalse: [^self error: 'TMSI must be four bytes']. type := GSM48IdentityType typeTMSI. self id: aTmsi. ] tmsi [ self type = GSM48IdentityType typeTMSI ifFalse: [^self error: 'Underlying type is not a TMSI']. ^ id ] id: anId [ id := anId ] type: aType [ type := aType ] type [ ^ type bitAnd: 2r111 ] writeOnDirect: aMsg [ type = GSM48IdentityType typeTMSI ifTrue: [self storeTMSIOn: aMsg] ifFalse: [self storeBCDIdentityOn: aMsg]. ] storeTMSIOn: aMsg [ aMsg putByte: 5; putByte: (type bitOr: 16rF0); putByteArray: id. ] storeBCDIdentityOn: aMsg [ | odd len head encoded bcds | odd := id size odd. "Calculate the length. We can fit two digits into one byte" len := odd ifTrue: [ (id size + 1) / 2 ] ifFalse: [ (id size / 2) + 1 ]. aMsg putByte: len. "Create the first data" head := ((id at: 1) digitValue) bitShift: 4. odd ifTrue: [ head := head bitOr: (1 bitShift: 3). ]. head := head bitOr: self type. aMsg putByte: head. "Encode everything from 2..n into a ByteArray of len - 1" bcds := OrderedCollection new. 2 to: id size do: [:pos | bcds add: (id at: pos) digitValue. ]. odd ifFalse: [ bcds add: 16r0F. ]. "now fold the bcds into and encoded array" encoded := OrderedCollection new. 1 to: bcds size by: 2 do: [:pos | | lower upper | lower := bcds at: pos. upper := bcds at: pos + 1. encoded add: ((upper bitShift: 4) bitOr: lower). ]. aMsg putByteArray: encoded asByteArray. ] ] GSM48SimpleData subclass: GSM48RejectCause [ GSM48RejectCause class [ causeImsiUnknownInHlr [ ^ 2r00000010 ] causeIllegalMS [ ^ 2r00000011 ] causeImsiUnknownInVLR [ ^ 2r00000100 ] causeIMEINotAccepted [ ^ 2r00000101 ] causeIllegalME [ ^ 2r00000110 ] causePLMNNotAllowed [ ^ 2r00001011 ] causeLocationAreaNotAllowed [ ^ 2r00001100 ] causeRoamingNotAllowedInLAC [ ^ 2r00001101 ] cuaseNetworkFailure [ ^ 2r00010001 ] causeCongestion [ ^ 2r00010110 ] cuaseServiceOptionNotSupported [ ^ 2r00100000 ] causeRequestedServiceOptionNotSubscribed [ ^ 2r00100001 ] causeServiceOptionTemporarilyOutOfOrder [ ^ 2r00100010 ] causeCallCannotBeIdentified [ ^ 2r00100110 ] causeSemanticallyIncorrectMessage [ ^ 2r01011111 ] causeInvalidMandatoryInformation [ ^ 2r01100000 ] causeMessageTypeNonExistentOrNotImplemented [ ^ 2r01100001 ] causeMessageTypeNotCompatibleWithProtocolState [ ^ 2r01100010 ] causeInformationElementNonExistentOrNotImplemented [ ^ 2r01100011 ] causeConditionalIEError [ ^ 2r01100100 ] causeMessageNotCompatibleWithProtocolState [ ^ 2r01100101 ] causeProtocolErrorUnspecified [ ^ 2r01101111 ] ] GSM48RejectCause class >> createDefault [ ^ self new cause: 11; yourself. ] cause [ ^ self data at: 1 ] cause: aCause [ self data: (ByteArray with: aCause). ] ] GSM48SimpleData subclass: GSM48AuthRand [ ] GSM48SimpleData subclass: GSM48AuthSRES [ ] GSM48SimpleTag subclass: GSM48FollowOn [ ] GSM48SimpleTag subclass: GSM48CTSPermission [ ] GSM48SimpleTag subclass: GSM48GroupCipherKeyNumber [ ] GSM48SimpleTag subclass: GSM48GPRSResumption [ ] GSM48SimpleData subclass: GSM48IdentityType [ "Ignore the spare values" GSM48IdentityType class >> typeIMSI [ ^ 2r001 ] GSM48IdentityType class >> typeIMEI [ ^ 2r010 ] GSM48IdentityType class >> typeIMEISV [ ^ 2r011 ] GSM48IdentityType class >> typeTMSI [ ^ 2r100 ] GSM48IdentityType class >> typeNone [ ^ 2r000 ] GSM48IdentityType class >> defaultValue [ ^ ByteArray with: self typeIMSI ] isIMSI [ ^ self data first = self class typeIMSI ] isIMEI [ ^ self data first = self class typeIMEI ] isIMEISV [ ^ self data first = self class typeIMEISV ] type: aType [ self data: (ByteArray with: aType) ] ] GSM48SimpleTag subclass: GSMRepeatInd [ ] GSM48SimpleTag subclass: GSMPriorityLevel [ ] Object subclass: GSMBitField [ | byte | GSMBitField class >> fromByte: aByte [ ^ self new byte: aByte; yourself ] GSMBitField class >> initialize [ self bitDefinition do: [:each | self compile: '%1 [ ^ self bitsFrom: (%2 to: %3) ]' % {each first. each second. each third}; compile: '%1: aVal [ self atBits: (%2 to: %3) put: aVal]' % {each first. each second. each third}. ] ] data [ ^ byte ] byte: aByte [ byte := aByte ] bitsFrom: interval [ | res mask | "Build the mask" mask := 0. interval do: [:each | mask := mask bitAt: each put: 1]. "And with the value and shift" res := (byte bitAnd: mask) bitShift: (interval first - 1) negated. ^ res ] atBits: interval put: aVal [ | shifted | aVal highBit > interval last ifTrue: [ ^ self error: 'Value bigger than interval'. ]. shifted := aVal bitShift: interval first - 1. interval do: [:each | byte := byte bitAt: each put: (shifted bitAt: each)]. ] ] GSMBitField subclass: GSMBearerCapOctet3 [ GSMBearerCapOctet3 class [ radioChReqReserved [ ^ 2r00 ] radioChReqFullRateOnly [ ^ 2r01 ] radioChReqDualHalfPref [ ^ 2r10 ] radioChReqDualFullPref [ ^ 2r11 ] radioCodStdGSM [ ^ 2r0 ] radioCodStdReserved [ ^ 2r1 ] transferModeCircuit [ ^ 2r0 ] transferModePacket [ ^ 2r1 ] transferCapSpeech [ ^ 2r000 ] transferCapUnrest [ ^ 2r001 ] transferCap31khzPlmn [ ^ 2r010 ] transferCapFacsimileGroup3 [ ^ 2r011 ] transferCapOtherITC [ ^ 2r101 ] "see Octet 5a" transferCapReserved [ ^ 2r111 ] bitDefinition [ "Bit definition of Octet3" ^ OrderedCollection new add: #('informationTransferCapability' 1 3); add: #('transferMode' 4 4); add: #('codingStandard' 5 5); add: #('radioChannelRequirement' 6 7); yourself ] ] ] GSMBitField subclass: GSMBearerCapOctet3a [ GSMBearerCapOctet3a class [ codingForTransferCapability [ ^ 2r0 ] codingForOtherExtensions [ ^ 2r1 ] ctmTextTelephonyNotSupported [ ^ 2r0 ] ctmTextTelephonySupported [ ^ 2r1 ] speechFullRateVersion1 [ ^ 2r0000 ] speechFullRateVersion2 [ ^ 2r0010 ] speechFullRateVersion3 [ ^ 2r0100 ] speechHalfRateVersion1 [ ^ 2r0001 ] speechHalfRateVersion3 [ ^ 2r0101 ] bitDefinition [ ^ OrderedCollection new add: #('speechVersionIndication' 1 4); add: #('spare' 5 5); add: #('ctm' 6 6); add: #('coding' 7 7); yourself ] ] ] GSMBearerCapOctet3a subclass: GSMBearerCapOctet3b [ GSMBearerCapOctet3b class [ bitDefinition [ "There is no CTM in this directtion" ^ OrderedCollection new add: #('speechVersionIndication' 1 4); add: #('spare' 5 6); add: #('coding' 7 7); yourself ] ] ] Object subclass: GSMBearerCapDecoderBase [ | octet3 | GSMBearerCapDecoderBase class >> parse: aStream [ ^ self new parse: aStream; checkEndOfStream: aStream; yourself ] octet3 [ ^ octet3 ] parse: aStream [ ^ self parseOctet3: aStream ] parseOctet3: aStream [ | byte | "I return true if there is more for octet3" octet3 := nil. "nothing left to read" aStream atEnd ifTrue: [ ^ false]. octet3 := GSMBearerCapOctet3 fromByte: aStream next. ^ (octet3 data bitAt: 8) = 0. ] parseOctets: aStream do: aBlock [ [aStream atEnd] whileFalse: [ | byte | byte := aStream next. aBlock value: byte. "Check if we are at an end here" (byte bitAt: 8) = 1 ifTrue: [ ^ self ] ] ] checkEndOfStream: aStream [ aStream atEnd ifFalse: [ ^ self error: 'Bearercaps not fully consumed.' ]. ] ] GSMBearerCapDecoderBase subclass: GSMBearerCapFromNetwork [ | octet3b | parse: aStream [ octet3b := nil. (self parseOctet3: aStream) ifTrue: [ self parseOctets: aStream do: [:each | self octet3b add: (GSMBearerCapOctet3b fromByte: each)] ]. ] octet3b [ ^ octet3b ifNil: [octet3b := OrderedCollection new] ] ] GSMBearerCapDecoderBase subclass: GSMBearerCapFromMS [ | octet3a | parse: aStream [ octet3a := nil. (self parseOctet3: aStream) ifTrue:[ self parseOctets: aStream do: [:each | self octet3a add: (GSMBearerCapOctet3a fromByte: each)]. ] ] octet3a [ ^ octet3a ifNil: [octet3a := OrderedCollection new] ] ] GSM48DataHolder subclass: GSMBearerCap [ "GSM 04.08 Table 10.5.102. Strings depend on other attributes" ] GSM48DataHolder subclass: GSMFacility [ ] GSM48DataHolder subclass: GSMProgress [ GSMProgress class [ codingStandardMask [ ^ 2r11 ] codingStandardQ931 [ ^ 2r00 ] codingStandardReservedInternational [ ^ 2r01 ] codingStandardNational [ ^ 2r10 ] codingStandardGSMToPLMNS [ ^ 2r11 ] locationMask [ ^ 2r1111 ] locationUser [ ^ 2r0000 ] locationPrivateNetLocalUser [ ^ 2r0001 ] locationPublicNetLocalUser [ ^ 2r0010 ] locationPublicNetRemoteUser [ ^ 2r0100 ] locationPrivateNetRemoteUser [ ^ 2r0101 ] locationNetBeyondInterworkingPoint [ ^ 2r1010 ] progressMask [ ^ 2r1111111 ] progressCallNotEndToEnd [ ^ 2r0000001 ] progressDestNotInISDN [ ^ 2r0000010 ] progressOrigNotInISDN [ ^ 2r0001000 ] progressCallReturnedToISDN [ ^ 2r0100000 ] progressQueueing [ ^ 2r1000000 ] ] GSMProgress class >> createDefault [ ^ self new data: #(2r11101010 2r10000001) asByteArray; yourself ] isGSMToPLMNS [ ^ self coding = self class codingStandardGSMToPLMNS. ] coding [ ^ ((data at: 1) bitShift: -5) bitAnd: 2r11 ] coding: aCode [ | code | code := data first bitClear: self class codingStandardMask. code := code bitOr: ((aCode bitAnd: 2r11) bitShift: 5). data at: 1 put: code. ] location [ ^ (data at: 1) bitAnd: 2r1111. ] location: aLoc [ | loc | loc := data first bitClear: self class locationMask. loc := loc bitOr: (aLoc bitAnd: 2r11). data at: 1 put: loc ] progress [ ^ (data at: 2) bitAnd: 2r1111111 ] progress: aProgress [ | prog | prog := data second bitClear: self class progressMask. prog := prog bitOr: (aProgress bitAnd: 2r1111111). data at: 2 put: prog. ] ] GSM48SimpleData subclass: GSMSignal [ | signal | ] Object subclass: GSMNumberingPlan [ GSMNumberingPlan class >> planUnknown [ ^ 0 ] GSMNumberingPlan class >> planISDN [ ^ 1 ] GSMNumberingPlan class >> planData [ ^ 3 ] GSMNumberingPlan class >> planTelex [ ^ 4 ] GSMNumberingPlan class >> planNational [ ^ 8 ] GSMNumberingPlan class >> planPrivate [ ^ 9 ] GSMNumberingPlan class >> planReserved [ ^ 15 ] ] Object subclass: GSMNumberDigits [ GSMNumberDigits class [ | digitMap reverseMap | ] GSMNumberDigits class >> mapDigit: aBinary [ ^ self digitMap at: aBinary asInteger + 1. ] GSMNumberDigits class >> digitMap: aDigit [ ^ self reverseMap at: aDigit. ] GSMNumberDigits class >> digitMap [ ^ digitMap ifNil: [ digitMap := Dictionary new. 1 to: 10 do: [:each | digitMap at: each put: (each + 48 - 1) asCharacter. ]. digitMap at: 11 put: $*. digitMap at: 12 put: $#. digitMap at: 13 put: $a. digitMap at: 14 put: $b. digitMap at: 15 put: $c. digitMap at: 16 put: $Z. digitMap yourself. ]. ] GSMNumberDigits class >> reverseMap [ ^ reverseMap ifNil: [ reverseMap := Dictionary new. self digitMap associationsDo: [:each | reverseMap at: each value put: (each key - 1). ]. reverseMap yourself. ]. ] GSMNumberDigits class >> decodeFrom: anArray [ ^ self decodeFromStream: anArray readStream. ] GSMNumberDigits class >> decodeFromStream: aStream [ | str | str := WriteStream on: String new. [aStream atEnd] whileFalse: [ | in tmp char | in := aStream next. tmp := in bitAnd: 16r0F. str nextPut: (self mapDigit: tmp). tmp := (in bitAnd: 16rF0) bitShift: -4. char := (self mapDigit: tmp). char = $Z ifFalse: [ str nextPut: char. ]. ]. ^ str contents ] GSMNumberDigits class >> encodeFrom: aNumber [ | str | str := WriteStream on: (ByteArray new). self encodeData: aNumber on: str. ^ str contents ] GSMNumberDigits class >> encodeData: aNumber on: aStr [ | digits | digits := OrderedCollection new. aNumber do: [:digit | digits add: (self digitMap: digit). ]. digits size odd ifTrue: [ digits add: 16rF. ]. "Create the binary structure" 1 to: digits size by: 2 do: [:each | | low high | low := digits at: each. high := digits at: each + 1. aStr nextPut: (low bitOr: (high bitShift: 4)). ]. ] ] GSM48DataHolder subclass: GSMCalledBCDNumber [ "For PCS1900 it is 19 in total, in theory up to 43. It depends on the direction as well" GSMCalledBCDNumber class >> spec [ ^ '10.5.4.7' ] GSMCalledBCDNumber class [ typeUnknown [ ^ 2r000 ] typeInternational [ ^ 2r001 ] typeNational [ ^ 2r010 ] typeNetworkSpecific [ ^ 2r011 ] typeDedicatedAccess [ ^ 2r100 ] planUnknown [ ^ 2r0000 ] planISDN [ ^ 2r0001 ] planData [ ^ 2r0011 ] planTelex [ ^ 2r0100 ] planNational [ ^ 2r1000 ] planPrivate [ ^ 2r1001 ] ] numberType [ ^ ((data at: 1) bitAnd: 16r70) bitShift: -4. ] numberPlan [ ^ (data at: 1) bitAnd: 16r0F ] number [ ^ GSMNumberDigits decodeFromStream: (data readStream skip: 1). ] encode: aType plan: aPlan nr: aNr [ | str tmp | str := WriteStream on: ByteArray new. tmp := 16r80. tmp := tmp bitOr: ((aType bitAnd: 16r7) bitShift: 4). tmp := tmp bitOr: ((aPlan bitAnd: 16rF) bitShift: 0). str nextPut: tmp. GSMNumberDigits encodeData: aNr on: str. self data: str contents. ] ] GSM48DataHolder subclass: GSMCalledSubBCDNumber [ ] GSM48DataHolder subclass: GSMCallingBCDNumber [ ] GSM48DataHolder subclass: GSMCallingSubBCDNumber [ ] GSM48DataHolder subclass: GSMRedirectingBCDNumber [ ] GSM48DataHolder subclass: GSMRedirectingSubBCDNumber [ ] GSM48DataHolder subclass: GSMLLCompability [ ] GSM48DataHolder subclass: GSMHLCompability [ ] GSM48DataHolder subclass: GSMUserUser [ ] GSM48DataHolder subclass: GSMSSVersionInd [ ] GSM48SimpleTag subclass: GSMClirSuppression [ ] GSM48SimpleTag subclass: GSMClirInvocation [ ] GSM48DataHolder subclass: GSMCCCapabilities [ "TODO: How to handle things that are specified like this but different in reality? The code should be able to be uses as both validation and real world parsing code." GSMCCCapabilities class >> strictlyValidSizes [ ^ 1 to: 1 ] ] GSM48DataHolder subclass: GSMConnectedNumber [ ] GSM48DataHolder subclass: GSMConnectedSubNumber [ ] GSM48DataHolder subclass: GSMAllowedActions [ ] GSM48DataHolder subclass: GSM48Cause [ ] GSM48DataHolder subclass: GSMAlertingPattern [ ] GSM48SimpleData subclass: GSM48Callstate [ ] GSM48DataHolder subclass: GSM48AuxillaryStates [ ] GSM48SimpleData subclass: GSMRRCause [ GSMRRCause class >> causeNormalEvent [ ^ 2r00000000 ] GSMRRCause class >> causeAbnormalRelUnspec [ ^ 2r00000001 ] GSMRRCause class >> causeAbnormalRelUnacc [ ^ 2r00000010 ] GSMRRCause class >> causeAbnormalRelTimer [ ^ 2r00000011 ] GSMRRCause class >> causeAbnormalRelInact [ ^ 2r00000100 ] GSMRRCause class >> causePreemptiveRelease [ ^ 2r00000101 ] GSMRRCause class >> causeHandoverImpossible [ ^ 2r00001000 ] GSMRRCause class >> causeChannelModeUnacc [ ^ 2r00001001 ] GSMRRCause class >> causeFrequencyNotImpl [ ^ 2r00001010 ] GSMRRCause class >> causeCallAlreadyCleared [ ^ 2r01000001 ] GSMRRCause class >> causeSemanticallyIncorr [ ^ 2r01011111 ] GSMRRCause class >> causeInvalidMandInfo [ ^ 2r01100000 ] GSMRRCause class >> causeMessageTypeNotExist [ ^ 2r01100001 ] GSMRRCause class >> causeMessageTypeIncompat [ ^ 2r01100010 ] GSMRRCause class >> causeConditionalIEError [ ^ 2r01100100 ] GSMRRCause class >> causeNoCellAllocAvail [ ^ 2r01100101 ] GSMRRCause class >> causeProtocolErrorUnspec [ ^ 2r01101111 ] GSMRRCause class >> defaultValue [ ^ ByteArray with: 0 ] ] GSM48SimpleData subclass: GSMStreamIdentifier [ ] GSM48DataHolder subclass: GSMSupportedCodecs [ ] GSM48SimpleTag subclass: GSMRedial [ ] GSM48SimpleData subclass: GSMNetworkCallControlCap [ ] GSM48SimpleData subclass: GSMCauseNoCLI [ ] GSM48DataHolder subclass: GSMBackupBearerCapability [ ] GSM48DataHolder subclass: GSM48BARange [ ] GSM48DataHolder subclass: GSM48GroupChannelDescription [ ] GSM48SimpleData subclass: GSM48CellChanelDescription [ ] GSM48DataHolder subclass: GSM48BAListPref [ ] GSM48DataHolder subclass: GSM48NetworkName [ ] GSM48NetworkName subclass: GSM48ShortName [ ] GSM48SimpleData subclass: GSM48TimeZone [ ] GSM48SimpleData subclass: GSM48TimeZoneAndTime [ ] GSM48DataHolder subclass: GSM48LSAIdentifier [ ] GSM48DataHolder subclass: GSM48DaylightSavingTime [ ] Osmo.TLVParserBase subclass: GSM48MSG [ | seq ti | GSM48MSG class >> initialize [ "Initialize all variables" self tlvDescription do: [:each | each instVarName isNil ifTrue: [ ^ self error: '%1 unknown instVarName for parseClass: %2' % {self name displayString. each parseClass name displayString.}]. each isOptional ifFalse: [self addMandatory: each instVarName with: each parseClass] ifTrue: [self addOptional: each instVarName with: each parseClass]. ] ] GSM48MSG class >> addVariable: aName [ "Check if the variable exists, otherwise add it" (self instVarNames includes: aName) ifFalse: [ self addInstVarName: aName. ]. ] GSM48MSG class >> addMandatory: aName with: aClass [ self addVariable: aName. self compile: '%1 [ ^ %1 ifNil: [%1 := %2 createDefault.]]' % {aName asString. aClass}. ] GSM48MSG class >> addOptional: aName with: aClass [ self addVariable: aName. self compile: '%1 [ ^ %1 ]' % {aName asString}. self compile: '%1OrDefault [ ^ %1 ifNil: [%1 := %2 createDefault.]]' % {aName asString. aClass}. ] GSM48MSG class >> isCompatible: classType msgType: messageType [ | localType | "Ignore the base classes." self isGSMBaseclass ifTrue: [^false]. localType := classType bitAnd: 16r0F. ^ (self classType = localType) and: [self messageType = messageType]. ] GSM48MSG class >> decode: aStream [ | classType messageType | classType := aStream next. messageType := aStream next bitAnd: 16r3F. aStream skip: -2. GSM48MSG allSubclassesDo: [:each | (each isCompatible: classType msgType: messageType) ifTrue: [ ^ each parseFrom: aStream. ]. ]. ^self error: 'No one handles: ', classType asString, ' and: ', messageType asString. ] GSM48MSG class >> parseFrom: aStream [ | res dat | res := self new. res ti: (aStream next bitShift: -4). res seq: (aStream next bitShift: -6). "This is messy. The GSM04.80 spec had the great idea of adding tagged mandatory items and we need to deal with it here." self tlvDescription do: [:each | each isMandatory ifTrue: [res parseMandatory: aStream with: each]. each isOptional ifTrue: [res parseOptional: aStream with: each]. ]. "TODO: Complain if we have not consumed everything" aStream atEnd ifFalse: [ self error: 'Every byte should be consumed: "%1"' % {aStream}. ]. ^ res ] parseMandatory: aStream with: tlvDescription [ tlvDescription isForcedTag ifTrue: [ "TODO: elementId..." aStream next = tlvDescription parseClass elementId ifFalse: [ ^ self error: 'Mandatory Tagged Element %1 not present.' % {tlvDescription instVarName asString->tlvDescription parseClass}. ]. ]. "TODO: use doParse here...." self instVarNamed: tlvDescription instVarName put: (tlvDescription parseClass parseFrom: aStream). ] parseOptional: aStream with: tlvDescription [ | tag clazz len | aStream atEnd ifTrue: [^nil]. clazz := tlvDescription parseClass. tag := aStream peek bitAnd: clazz ieMask. tag = clazz elementId ifFalse: [^nil]. len := clazz length: aStream. aStream skip: 1. "treat the T only tags specially" len = 0 ifTrue: [ self instVarNamed: tlvDescription instVarName put: (clazz initWithData: len).] ifFalse: [ self instVarNamed: tlvDescription instVarName put: (clazz parseFrom: aStream).]. ] writeOn: aMsg [ | type classType | type := self seq bitShift: 6. type := type bitOr: self class messageType. "Write the header. Skip Ind, Sequence are hardcoded" classType := self ti bitShift: 4. classType := classType bitOr: self class classType. aMsg putByte: classType. aMsg putByte: type. "Write all Mandatory parts" self class tlvDescription do: [:each | each isMandatory ifTrue: [ | tmp | tmp := self perform: each instVarName. each isForcedTag ifTrue: [tmp writeOn: aMsg] ifFalse: [tmp writeOnDirect: aMsg]]. each isOptional ifTrue: [ | tmp | tmp := self perform: each instVarName. tmp ifNotNil: [ tmp writeOn: aMsg. ]. ]. "TODO: Handle the Conditionals better here.." each isConditional ifTrue: [ | tmp | "Only write if it is already present" tmp := self instVarNamed: each instVarName. tmp ifNotNil: [ tmp writeOn: aMsg. ]. ]. ] ] seq: aSeq [ seq := aSeq. ] seq [ ^ seq ifNil: [ 0 ] ] ti: aTi [ ti := aTi. ] ti [ "by default treat it like a spare" ^ 0 ] type [ ^ self class messageType ] ] GSM48MSG subclass: GSM48MMMessage [ GSM48MMMessage class >> isGSMBaseclass [ ^ self = GSM48MMMessage ] GSM48MMMessage class >> classType [ ^ 16r5 ] GSM48MMMessage class >> msgLUAcc [ ^ 16r02 ] GSM48MMMessage class >> msgLURej [ ^ 16r04 ] GSM48MMMessage class >> msgLUReq [ ^ 16r08 ] GSM48MMMessage class >> msgIdRes [ ^ 16r19 ] GSM48MMMessage class >> msgIdReq [ ^ 16r18 ] GSM48MMMessage class >> msgAuRej [ ^ 16r11 ] GSM48MMMessage class >> msgAuReq [ ^ 16r12 ] GSM48MMMessage class >> msgAuRes [ ^ 16r14 ] GSM48MMMessage class >> msgCMAccept [ ^ 16r21 ] GSM48MMMessage class >> msgCMReject [ ^ 16r22 ] GSM48MMMessage class >> msgCMReq [ ^ 16r24 ] GSM48MMMessage class >> msgIMSIDetach [ ^ 16r01 ] GSM48MMMessage class >> msgTMSIReallocationCommand [ ^ 2r11010 ] GSM48MMMessage class >> msgTMSIReallocationComplete [ ^ 2r11011 ] GSM48MMMessage class >> msgMMInfo [ ^ 2r110010 ] ] GSM48MSG subclass: GSM48CCMessage [ GSM48CCMessage class >> isGSMBaseclass [ ^ self = GSM48CCMessage ] GSM48CCMessage class >> classType [ ^ 16r3 ] GSM48CCMessage class >> msgAlerting [ ^ 2r000001 ] GSM48CCMessage class >> msgConfirmed [ ^ 2r001000 ] GSM48CCMessage class >> msgProceeding [ ^ 2r000010 ] GSM48CCMessage class >> msgConnect [ ^ 2r000111 ] GSM48CCMessage class >> msgConnectAck [ ^ 2r001111 ] GSM48CCMessage class >> msgEmergencySetup [ ^ 2r001110 ] GSM48CCMessage class >> msgProgress [ ^ 2r000011 ] GSM48CCMessage class >> msgCCEst [ ^ 2r000100 ] GSM48CCMessage class >> msgCCEstCnf [ ^ 2r000110 ] GSM48CCMessage class >> msgRecall [ ^ 2r001011 ] GSM48CCMessage class >> msgStartCC [ ^ 2r001001 ] GSM48CCMessage class >> msgSetup [ ^ 2r000101 ] GSM48CCMessage class >> msgModify [ ^ 2r010111 ] GSM48CCMessage class >> msgModifyComplete [ ^ 2r011111 ] GSM48CCMessage class >> msgModifyReject [ ^ 2r010011 ] GSM48CCMessage class >> msgUserInformation [ ^ 2r010000 ] GSM48CCMessage class >> msgHold [ ^ 2r011000 ] GSM48CCMessage class >> msgHoldAck [ ^ 2r011001 ] GSM48CCMessage class >> msgHoldReject [ ^ 2r011010 ] GSM48CCMessage class >> msgRetrieve [ ^ 2r011100 ] GSM48CCMessage class >> msgRetrieveAck [ ^ 2r011101 ] GSM48CCMessage class >> msgRetrieveReject [ ^ 2r011110 ] GSM48CCMessage class >> msgDisconnect [ ^ 2r100101 ] GSM48CCMessage class >> msgRelease [ ^ 2r101101 ] GSM48CCMessage class >> msgReleaseCompl [ ^ 2r101010 ] GSM48CCMessage class >> msgCongestionCtrl [ ^ 2r111001 ] GSM48CCMessage class >> msgNotify [ ^ 2r111110 ] GSM48CCMessage class >> msgStatus [ ^ 2r111101 ] GSM48CCMessage class >> msgStatusEnquiry [ ^ 2r110100 ] GSM48CCMessage class >> msgStartDTMF [ ^ 2r110101 ] GSM48CCMessage class >> msgStopDTMF [ ^ 2r110001 ] GSM48CCMessage class >> msgStopDTMFAck [ ^ 2r110010 ] GSM48CCMessage class >> msgStartDTMFAck [ ^ 2r110110 ] GSM48CCMessage class >> msgStartDTMFReject [ ^ 2r110111 ] GSM48CCMessage class >> msgFacility [ ^ 2r111010 ] ti [ ^ ti ifNil: [ 0 ] ] ] GSM48MSG subclass: GSM48RRMessage [ GSM48RRMessage class >> isGSMBaseclass [ ^ self = GSM48RRMessage ] GSM48RRMessage class >> classType [ ^ 16r6 ] GSM48RRMessage class >> msgInitRequest [ ^ 2r00111100 ] GSM48RRMessage class >> msgAddAssignment [ ^ 2r00111011 ] GSM48RRMessage class >> msgImmAssignment [ ^ 2r00111111 ] GSM48RRMessage class >> msgImmAssignmentExt [ ^ 2r00111010 ] GSM48RRMessage class >> msgCipherModeCommand [ ^ 2r00110101 ] GSM48RRMessage class >> msgCipherModeComplete [ ^ 2r00110010 ] GSM48RRMessage class >> msgConfigChangeCommand [ ^ 2r00110000 ] GSM48RRMessage class >> msgConfigChangeAck [ ^ 2r00110001 ] GSM48RRMessage class >> msgConfigChangeReject [ ^ 2r00110011 ] GSM48RRMessage class >> msgAssignmentCommand [ ^ 2r00101110 ] GSM48RRMessage class >> msgAssignmentComplete [ ^ 2r00101001 ] GSM48RRMessage class >> msgAssignmentFailure [ ^ 2r00101111 ] GSM48RRMessage class >> msgHandoverCommand [ ^ 2r00101011 ] GSM48RRMessage class >> msgHandoverComplete [ ^ 2r00101100 ] GSM48RRMessage class >> msgHandoverFailure [ ^ 2r00101101 ] GSM48RRMessage class >> msgCellChangeOrder [ ^ 2r00001000 ] GSM48RRMessage class >> msgPdchAssignmentCommand [ ^ 2r00100011 ] GSM48RRMessage class >> msgChannelRelease [ ^ 2r00001101 ] GSM48RRMessage class >> msgPartialRelease [ ^ 2r00001010 ] GSM48RRMessage class >> msgPartialReleaseComplete [ ^ 2r00001111 ] GSM48RRMessage class >> msgPagingRequestType1 [ ^ 2r00100001 ] GSM48RRMessage class >> msgPagingRequestType2 [ ^ 2r00100010 ] GSM48RRMessage class >> msgPagingRequestType3 [ ^ 2r00100100 ] GSM48RRMessage class >> msgPagingResponse [ ^ 2r00100111 ] GSM48RRMessage class >> msgNotificationNch [ ^ 2r00100000 ] GSM48RRMessage class >> msgNotificationFacch [ ^ 2r00100101 ] GSM48RRMessage class >> msgNotificationResponse [ ^ 2r00100110 ] GSM48RRMessage class >> msgSystemInformation8 [ ^ 2r00011000 ] GSM48RRMessage class >> msgSystemInformation1 [ ^ 2r00011001 ] GSM48RRMessage class >> msgSystemInformation2 [ ^ 2r00011010 ] GSM48RRMessage class >> msgSystemInformation3 [ ^ 2r00011011 ] GSM48RRMessage class >> msgSystemInformation4 [ ^ 2r00011100 ] GSM48RRMessage class >> msgSystemInformation5 [ ^ 2r00011101 ] GSM48RRMessage class >> msgSystemInformation6 [ ^ 2r00011110 ] GSM48RRMessage class >> msgSystemInformation7 [ ^ 2r00011111 ] GSM48RRMessage class >> msgSystemInformation2bis [ ^ 2r00000010 ] GSM48RRMessage class >> msgSystemInformation2ter [ ^ 2r00000011 ] GSM48RRMessage class >> msgSystemInformation5bis [ ^ 2r00000101 ] GSM48RRMessage class >> msgSystemInformation5ter [ ^ 2r00000110 ] GSM48RRMessage class >> msgSystemInformation9 [ ^ 2r00000100 ] GSM48RRMessage class >> msgSystemInformation13 [ ^ 2r00000000 ] GSM48RRMessage class >> msgSystemInformation16 [ ^ 2r00111101 ] GSM48RRMessage class >> msgSystemInformation17 [ ^ 2r00111110 ] GSM48RRMessage class >> msgChannelModeModify [ ^ 2r00010000 ] GSM48RRMessage class >> msgRRStatus [ ^ 2r00010010 ] GSM48RRMessage class >> msgChannelModeModifyAck [ ^ 2r00010111 ] GSM48RRMessage class >> msgFrequencyRedefinition [ ^ 2r00010100 ] GSM48RRMessage class >> msgMeasurementReport [ ^ 2r00010101 ] GSM48RRMessage class >> msgClassmarkChange [ ^ 2r00010110 ] GSM48RRMessage class >> msgClassmarkEnquiry [ ^ 2r00010011 ] GSM48RRMessage class >> msgExtendedMeasurementReport [ ^ 2r00110110 ] GSM48RRMessage class >> msgExtendedMeasurementOrder [ ^ 2r00110111 ] GSM48RRMessage class >> msgGPRSSuspensionRequest [ ^ 2r00110100 ] GSM48RRMessage class >> msgVGCSUplinkGrant [ ^ 2r00001001 ] GSM48RRMessage class >> msgUplinkRelease [ ^ 2r00001110 ] GSM48RRMessage class >> msgUplinkFree [ ^ 2r00001100 ] GSM48RRMessage class >> msgTalkerIndication [ ^ 2r00010001 ] GSM48RRMessage class >> msgApplicationInformation [ ^ 2r00111000 ] ] GSM48MSG subclass: GSM48SSMessage [ GSM48SSMessage class >> isGSMBaseclass [ ^ self = GSM48SSMessage ] GSM48SSMessage class >> classType [ ^ 2r1011 ] GSM48SSMessage class >> msgReleaseCompl [ ^ 2r101010 ] GSM48SSMessage class >> msgFacility [ ^ 2r111010 ] GSM48SSMessage class >> msgRegister [ ^ 2r111011 ] ti [ ^ ti ifNil: [ 0 ] ] ] GSM48MMMessage subclass: GSM48LURequest [ GSM48LURequest class >> messageType [ ^ self msgLUReq ] GSM48LURequest class >> tlvDescription [ ^ OrderedCollection new add: GSM48KeySeqLuType asTLVDescription; add: GSM48Lai asTLVDescription; add: GSM48Classmark1 asTLVDescription; add: GSM48MIdentity asTLVDescription; yourself. ] ] GSM48MMMessage subclass: GSM48LUAccept [ GSM48LUAccept class >> messageType [ ^ self msgLUAcc ] GSM48LUAccept class >> tlvDescription [ ^ OrderedCollection new add: GSM48Lai asTLVDescription; add: (GSM48MIdentity asTLVDescription beOptional; yourself); add: (GSM48FollowOn asTLVDescription beOptional; yourself); add: (GSM48CTSPermission asTLVDescription beOptional; yourself); yourself ] ] GSM48MMMessage subclass: GSM48LUReject [ GSM48LUReject class >> messageType [ ^ self msgLURej ] GSM48LUReject class >> tlvDescription [ ^ OrderedCollection new add: GSM48RejectCause asTLVDescription; yourself ] ] GSM48MMMessage subclass: GSM48AuthRej [ GSM48AuthRej class >> messageType [ ^ self msgAuRej ] GSM48AuthRej class >> tlvDescription [ ^ #() ] ] GSM48MMMessage subclass: GSM48AuthReq [ GSM48AuthReq class >> messageType [ ^ self msgAuReq ] GSM48AuthReq class >> tlvDescription [ ^ OrderedCollection new add: GSM48KeySeqLuType asTLVDescription; add: GSM48AuthRand asTLVDescription; yourself ] ] GSM48MMMessage subclass: GSM48AuthResp [ GSM48AuthResp class >> messageType [ ^ self msgAuRes ] GSM48AuthResp class >> tlvDescription [ ^ OrderedCollection new add: GSM48AuthSRES asTLVDescription; yourself ] ] GSM48MMMessage subclass: GSM48IdentityReq [ GSM48IdentityReq class >> messageType [ ^ self msgIdReq ] GSM48IdentityReq class >> tlvDescription [ ^ OrderedCollection new add: GSM48IdentityType asTLVDescription; yourself ] ] GSM48MMMessage subclass: GSM48IdentityResponse [ GSM48IdentityResponse class >> messageType [ ^ self msgIdRes ] GSM48IdentityResponse class >> tlvDescription [ ^ OrderedCollection new add: GSM48MIdentity asTLVDescription; yourself ] ] GSM48MMMessage subclass: GSM48CMServiceAccept [ GSM48CMServiceAccept class >> messageType [ ^ self msgCMAccept ] GSM48CMServiceAccept class >> tlvDescription [ ^ OrderedCollection new ] ] GSM48MMMessage subclass: GSM48CMServiceReq [ GSM48CMServiceReq class >> messageType [ ^ self msgCMReq ] GSM48CMServiceReq class >> tlvDescription [ ^ OrderedCollection new add: GSM48KeySeqLuType asTLVDescription; add: GSM48Classmark2 asTLVDescription; add: GSM48MIdentity asTLVDescription; add: (GSMPriorityLevel asTLVDescription beOptional; yourself); yourself ] ] GSM48MMMessage subclass: GSM48CMServiceReject [ GSM48CMServiceReject class >> messageType [ ^ self msgCMReject ] GSM48CMServiceReject class >> tlvDescription [ ^ OrderedCollection new add: GSM48RejectCause asTLVDescription; yourself ] ] GSM48MMMessage subclass: GSM48IMSIDetachInd [ GSM48IMSIDetachInd class >> messageType [ ^ self msgIMSIDetach ] GSM48IMSIDetachInd class >> tlvDescription [ ^ OrderedCollection new add: GSM48Classmark1 asTLVDescription; add: GSM48MIdentity asTLVDescription; yourself ] ] GSM48MMMessage subclass: GSM48TMSIReallocationCommand [ GSM48TMSIReallocationCommand class >> messageType [ ^ self msgTMSIReallocationCommand ] GSM48TMSIReallocationCommand class >> tlvDescription [ ^ OrderedCollection new add: GSM48Lai asTLVDescription; add: GSM48MIdentity asTLVDescription; yourself ] ] GSM48MMMessage subclass: GSM48TMSIReallocationComplete [ GSM48TMSIReallocationComplete class >> messageType [ ^ self msgTMSIReallocationComplete ] GSM48TMSIReallocationComplete class >> tlvDescription [ ^ OrderedCollection new ] ] GSM48MMMessage subclass: GSM48MMInformation [ GSM48MMInformation class >> messageType [ ^ self msgMMInfo ] GSM48MMInformation class >> tlvDescription [ ^ OrderedCollection new add: (GSM48NetworkName asTLVDescription beOptional; yourself); add: (GSM48ShortName asTLVDescription beOptional; yourself); add: (GSM48TimeZone asTLVDescription beOptional; yourself); add: (GSM48TimeZoneAndTime asTLVDescription beOptional; yourself); add: (GSM48LSAIdentifier asTLVDescription beOptional; yourself); add: (GSM48DaylightSavingTime asTLVDescription beOptional; yourself); yourself ] ] GSM48CCMessage subclass: GSM48CCSetup [ GSM48CCSetup class >> messageType [ ^ self msgSetup ] GSM48CCSetup class >> tlvDescription [ ^ OrderedCollection new add: (GSMRepeatInd asTLVDescription beOptional; yourself); add: (GSMBearerCap asTLVDescription beOptional; instVarName: #bearer1; yourself); add: (GSMBearerCap asTLVDescription beOptional; instVarName: #bearer2; yourself); add: (GSMFacility asTLVDescription beOptional; yourself); add: (GSMProgress asTLVDescription beOptional; yourself); add: (GSMSignal asTLVDescription beOptional; yourself); add: (GSMCallingBCDNumber asTLVDescription beOptional; yourself); add: (GSMCallingSubBCDNumber asTLVDescription beOptional; yourself); add: (GSMCalledBCDNumber asTLVDescription beOptional; yourself); add: (GSMCalledSubBCDNumber asTLVDescription beOptional; yourself); add: (GSMRedirectingBCDNumber asTLVDescription beOptional; yourself); add: (GSMRedirectingSubBCDNumber asTLVDescription beOptional; yourself); add: (GSMRepeatInd asTLVDescription beOptional; instVarName: #LLCInd; yourself); add: (GSMLLCompability asTLVDescription beOptional; instVarName: #llc1; yourself); add: (GSMLLCompability asTLVDescription beOptional; instVarName: #llc2; yourself); add: (GSMRepeatInd asTLVDescription beOptional; instVarName: #HLCInd; yourself); add: (GSMHLCompability asTLVDescription beOptional; instVarName: #hlc1; yourself); add: (GSMHLCompability asTLVDescription beOptional; instVarName: #hlc2; yourself); add: (GSMUserUser asTLVDescription beOptional; yourself); "For MO call" add: (GSMSSVersionInd asTLVDescription beOptional; yourself); add: (GSMClirSuppression asTLVDescription beOptional; yourself); add: (GSMClirInvocation asTLVDescription beOptional; yourself); add: (GSMCCCapabilities asTLVDescription beOptional; yourself); add: (GSMFacility asTLVDescription beOptional; instVarName: #facilityCCBS; yourself); add: (GSMFacility asTLVDescription beOptional; instVarName: #facilityReca; yourself); add: (GSMStreamIdentifier asTLVDescription beOptional; yourself); add: (GSMSupportedCodecs asTLVDescription beOptional; yourself); add: (GSMRedial asTLVDescription beOptional; yourself); "For MT call" add: (GSMPriorityLevel asTLVDescription beOptional; yourself); add: (GSMAlertingPattern asTLVDescription beOptional; yourself); add: (GSMNetworkCallControlCap asTLVDescription beOptional; yourself); add: (GSMCauseNoCLI asTLVDescription beOptional; yourself); add: (GSMBackupBearerCapability asTLVDescription beOptional; yourself); yourself ] writeOn: aMsg [ "TODO: these are incomplete and wrong" "Implement the conditionals" (self bearer1 ~= nil and: [self bearer2 ~= nil]) ifTrue: [ self instVarNamed: #repeatInd put: GSMRepeatInd new. ] ifFalse: [ self instVarNamed: #repeatInd put: nil. ]. (self llc1 ~= nil and: [self llc2 ~= nil]) ifTrue: [ self instVarNamed: #LLCInd put: GSMRepeatInd new. ] ifFalse: [ self instVarNamed: #LLCInd put: nil. ]. (self hlc1 ~= nil and: [self hlc2 ~= nil]) ifTrue: [ self instVarNamed: #HLCInd put: GSMRepeatInd new. ] ifFalse: [ self instVarNamed: #HLCInd put: nil. ]. ^ super writeOn: aMsg. ] ] GSM48CCMessage subclass: GSM48CCProceeding [ GSM48CCProceeding class >> messageType [ ^ self msgProceeding ] GSM48CCProceeding class >> tlvDescription [ ^ OrderedCollection new add: (GSMRepeatInd asTLVDescription beOptional; yourself); add: (GSMBearerCap asTLVDescription beOptional; instVarName: #bearer1; yourself); add: (GSMBearerCap asTLVDescription beOptional; instVarName: #bearer2; yourself); add: (GSMFacility asTLVDescription beOptional; yourself); add: (GSMProgress asTLVDescription beOptional; yourself); add: (GSMPriorityLevel asTLVDescription beOptional; instVarName: #priorityGranted; yourself); add: (GSMNetworkCallControlCap asTLVDescription beOptional; instVarName: #networkCallControlCaps; yourself); yourself ] writeOn: aMsg [ (self bearer1 ~= nil and: [self bearer2 ~= nil]) ifTrue: [ self instVarNamed: #repeatInd put: GSMRepeatInd new. ] ifFalse: [ self instVarNamed: #repeatInd put: nil. ]. ^ super writeOn: aMsg. ] ] GSM48CCMessage subclass: GSM48CCAlerting [ GSM48CCAlerting class >> messageType [ ^ self msgAlerting ] GSM48CCAlerting class >> tlvDescription [ ^ OrderedCollection new add: (GSMFacility asTLVDescription beOptional; yourself); add: (GSMProgress asTLVDescription beOptional; yourself); add: (GSMUserUser asTLVDescription beOptional; yourself); "mobile station to network" add: (GSMSSVersionInd asTLVDescription beOptional; yourself); yourself ] ] GSM48CCMessage subclass: GSM48CCCallConfirmed [ GSM48CCCallConfirmed class >> messageType [ ^ self msgConfirmed ] GSM48CCCallConfirmed class >> tlvDescription [ ^ OrderedCollection new add: (GSMRepeatInd asTLVDescription beOptional; yourself); add: (GSMBearerCap asTLVDescription beOptional; instVarName: #bearer1; yourself); add: (GSMBearerCap asTLVDescription beOptional; instVarName: #bearer2; yourself); add: (GSM48Cause asTLVDescription beOptional; yourself); add: (GSMCCCapabilities asTLVDescription beOptional; yourself); yourself ] ] GSM48CCMessage subclass: GSM48CCConnect [ GSM48CCConnect class >> messageType [ ^ self msgConnect ] GSM48CCConnect class >> tlvDescription [ ^ OrderedCollection new add: (GSMFacility asTLVDescription beOptional; yourself); add: (GSMProgress asTLVDescription beOptional; yourself); add: (GSMConnectedNumber asTLVDescription beOptional; yourself); add: (GSMConnectedSubNumber asTLVDescription beOptional; yourself); add: (GSMUserUser asTLVDescription beOptional; yourself); add: (GSMSSVersionInd asTLVDescription beOptional; yourself); add: (GSMStreamIdentifier asTLVDescription beOptional; yourself); yourself ] ] GSM48CCMessage subclass: GSM48CCConnectAck [ GSM48CCConnectAck class >> messageType [ ^ self msgConnectAck ] GSM48CCConnectAck class >> tlvDescription [ ^ #() ] ] GSM48CCMessage subclass: GSM48CCDisconnect [ GSM48CCDisconnect class >> messageType [ ^ self msgDisconnect ] GSM48CCDisconnect class >> tlvDescription [ ^ OrderedCollection new add: GSM48Cause asTLVDescription; add: (GSMFacility asTLVDescription beOptional; yourself); add: (GSMProgress asTLVDescription beOptional; yourself); add: (GSMUserUser asTLVDescription beOptional; yourself); add: (GSMAllowedActions asTLVDescription beOptional; yourself); "MO addition" add: (GSMSSVersionInd asTLVDescription beOptional; yourself); yourself ] ] GSM48CCMessage subclass: GSM48CCRelease [ GSM48CCRelease class >> messageType [ ^ self msgRelease ] GSM48CCRelease class >> tlvDescription [ ^ OrderedCollection new add: (GSM48Cause asTLVDescription beOptional; yourself); add: (GSM48Cause asTLVDescription beOptional; instVarName: #secondCause; yourself); add: (GSMFacility asTLVDescription beOptional; yourself); add: (GSMUserUser asTLVDescription beOptional; yourself); add: (GSMSSVersionInd asTLVDescription beOptional; yourself); yourself ] ] GSM48CCMessage subclass: GSM48CCReleaseCompl [ GSM48CCReleaseCompl class >> messageType [ ^ self msgReleaseCompl ] GSM48CCReleaseCompl class >> tlvDescription [ ^ OrderedCollection new add: (GSM48Cause asTLVDescription beOptional; yourself); add: (GSMFacility asTLVDescription beOptional; yourself); add: (GSMUserUser asTLVDescription beOptional; yourself); add: (GSMSSVersionInd asTLVDescription beOptional; yourself); yourself ] ] GSM48CCMessage subclass: GSM48CCStatus [ GSM48CCStatus class >> messageType [ ^ self msgStatus ] GSM48CCStatus class >> tlvDescription [ ^ OrderedCollection new add: GSM48Cause asTLVDescription; add: GSM48Callstate asTLVDescription; add: (GSM48AuxillaryStates asTLVDescription beOptional; yourself); yourself ] ] GSM48CCMessage subclass: GSM48CCEmergencySetup [ GSM48CCEmergencySetup class >> messageType [ ^ self msgEmergencySetup ] GSM48CCEmergencySetup class >> tlvDescription [ ^ OrderedCollection new add: (GSMBearerCap asTLVDescription beOptional; yourself); yourself ] ] GSM48CCMessage subclass: GSM48CCProgress [ GSM48CCProgress class >> messageType [ ^self msgProgress ] GSM48CCProgress class >> tlvDescription [ ^OrderedCollection new add: GSMProgress asTLVDescription; add: (GSMUserUser asTLVDescription beOptional; minSize: 1 maxSize: 129; yourself); yourself ] ] GSM48RRMessage subclass: GSM48RRAssignmentComplete [ GSM48RRAssignmentComplete class >> messageType [ ^ self msgAssignmentComplete ] GSM48RRAssignmentComplete class >> tlvDescription [ ^ OrderedCollection new add: GSMRRCause asTLVDescription; yourself ] ] GSM48RRMessage subclass: GSM48RRHandoverCommand [ GSM48RRHandoverCommand class >> messageType [ ^ self msgHandoverCommand ] GSM48RRHandoverCommand class >> tlvDescription [ ^ OrderedCollection new add: GSM48CellDescription asTLVDescription; add: GSM48ChannelDescription2 asTLVDescription; add: GSM48HandoverReference asTLVDescription; add: GSM48PowerCommandAndAccess asTLVDescription; add: (GSM48SynchronizationInd asTLVDescription beOptional; yourself); add: (GSM48FrequencyShortList asTLVDescription beConditional; yourself); add: (GSM48FrequencyList asTLVDescription beConditional; yourself); add: (GSM48CellChanelDescription asTLVDescription beConditional; yourself); add: (GSM48MultislotAllocation asTLVDescription beConditional; yourself); add: (GSM48ChannelMode asTLVDescription instVarName: #channelSet1; beOptional; yourself); add: (GSM48ChannelMode asTLVDescription instVarName: #channelSet2; beOptional; yourself); add: (GSM48ChannelMode asTLVDescription instVarName: #channelSet3; beOptional; yourself); add: (GSM48ChannelMode asTLVDescription instVarName: #channelSet4; beOptional; yourself); add: (GSM48ChannelMode asTLVDescription instVarName: #channelSet5; beOptional; yourself); add: (GSM48ChannelMode asTLVDescription instVarName: #channelSet6; beOptional; yourself); add: (GSM48ChannelMode asTLVDescription instVarName: #channelSet7; beOptional; yourself); add: (GSM48ChannelMode asTLVDescription instVarName: #channelSet8; beOptional; yourself); add: (GSM48ChannelDescription asTLVDescription instVarName: #secondDescription; beOptional; yourself); add: (GSM48ChannelMode2 asTLVDescription instVarName: #secondMode; beOptional; yourself); add: (GSM48FrequencyChannelSequence asTLVDescription beConditional; yourself); add: (GSM48MobileAllocation asTLVDescription beConditional; yourself); add: (GSM48StartingTime asTLVDescription beOptional; yourself); add: (GSM48TimingDifference asTLVDescription beConditional; yourself); add: (GSM48TimingAdvance asTLVDescription beConditional; yourself); add: (GSM48FrequencyShortList asTLVDescription instVarName: #beforeTimeShort; beConditional; yourself); add: (GSM48FrequencyList asTLVDescription instVarName: #beforeTimeList; beConditional; yourself); add: (GSM48ChannelDescription2 asTLVDescription instVarName: #beforeTimeChannel; beOptional; yourself); add: (GSM48ChannelDescription asTLVDescription instVarName: #beforeTimeSecondChannel; beOptional; yourself); add: (GSM48FrequencyChannelSequence asTLVDescription instVarName: #beforeTimeFrequencySeq; beConditional; yourself); add: (GSM48MobileAllocation asTLVDescription instVarName: #beforeTimeTime; beConditional; yourself); add: (GSM48CipherModeSetting asTLVDescription beOptional; yourself); add: (GSM48VGCSTargetModeIndication asTLVDescription beOptional; yourself); add: (GSM48MultiRateConfiguration asTLVDescription beOptional; yourself); yourself ] ] GSM48RRMessage subclass: GSM48RRHandoverComplete [ GSM48RRHandoverComplete class >> messageType [ ^ self msgHandoverComplete ] GSM48RRHandoverComplete class >> tlvDescription [ ^ OrderedCollection new add: GSMRRCause asTLVDescription; add: (GSM48TimingDifference asTLVDescription beOptional; yourself); yourself ] ] GSM48RRMessage subclass: GSM48RRHandoverFailure [ GSM48RRHandoverFailure class >> messageType [ ^ self msgHandoverFailure ] GSM48RRHandoverFailure class >> tlvDescription [ ^ OrderedCollection new add: GSM48Cause asTLVDescription; yourself ] ] GSM48RRMessage subclass: GSM48RRImmediateAssignCommand [ GSM48RRImmediateAssignCommand class [ messageType [ ^ self msgImmAssignment ] ] GSM48RRImmediateAssignCommand class >> tlvDescription [ ^ OrderedCollection new add: GSM48PageAndDedicatedMode asTLVDescription; "TODO: properly handle conditionals" add: GSM48ChannelOrPacketDescription asTLVDescription; add: GSM48RequestReference asTLVDescription; add: GSM48TimingAdvance asTLVDescription; add: GSM48MobileAllocation asTLVDescription; add: (GSM48StartingTime asTLVDescription beOptional; yourself); add: GSM48IARestOctets asTLVDescription; yourself ] ] GSM48RRMessage subclass: GSM48RRChannelRelease [ GSM48RRChannelRelease class [ messageType [ ^ self msgChannelRelease ] ] GSM48RRChannelRelease class >> tlvDescription [ ^ OrderedCollection new add: GSMRRCause asTLVDescription; add: (GSM48BARange asTLVDescription beOptional; yourself); add: (GSM48GroupChannelDescription asTLVDescription beOptional; yourself); add: (GSM48GroupCipherKeyNumber asTLVDescription beConditional; yourself); add: (GSM48GPRSResumption asTLVDescription beOptional; yourself); add: (GSM48BAListPref asTLVDescription beOptional; yourself); yourself ] ] GSM48RRMessage subclass: GSM48RRCipheringModeCommand [ GSM48RRCipheringModeCommand class >> messageType [ ^self msgCipherModeCommand ] GSM48RRCipheringModeCommand class >> tlvDescription [ ^OrderedCollection new add: GSM48CipherModeSettingResponse asTLVDescription; yourself ] ] GSM48RRMessage subclass: GSM48RRCipheringModeComplete [ GSM48RRCipheringModeComplete class >> messageType [ ^self msgCipherModeComplete ] GSM48RRCipheringModeComplete class >> tlvDescription [ ^OrderedCollection new add: (GSM48MIdentity asTLVDescription beOptional; yourself); yourself ] ] GSM48RRMessage subclass: GSM48RRClassmarkChange [ GSM48RRClassmarkChange class >> messageType [ ^ self msgClassmarkChange ] GSM48RRClassmarkChange class >> tlvDescription [ ^ OrderedCollection new add: GSM48Classmark2 asTLVDescription; add: (GSM48Classmark3 asTLVDescription beConditional; yourself); yourself ] ] GSM48RRMessage subclass: GSM48RRPagingResponse [ GSM48RRPagingResponse class >> messageType [ ^ self msgPagingResponse ] GSM48RRPagingResponse class >> tlvDescription [ ^ OrderedCollection new add: GSM48KeySeqLuType asTLVDescription; add: GSM48Classmark2 asTLVDescription; add: GSM48MIdentity asTLVDescription; yourself. ] ] GSM48RRMessage subclass: GSM48RRChannelModeModify [ GSM48RRChannelModeModify class >> messageType [ ^ self msgChannelModeModify ] GSM48RRChannelModeModify class >> tlvDescription [ ^ OrderedCollection new add: GSM48ChannelDescription asTLVDescription; add: GSM48ChannelMode asTLVDescription; add: (GSM48VGCSTargetModeIndication asTLVDescription beOptional; yourself); add: (GSM48MultiRateConfiguration asTLVDescription beOptional; yourself); yourself ] ] GSM48RRMessage subclass: GSM48RRChannelModeModifyAck [ GSM48RRChannelModeModifyAck class >> messageType [ ^ self msgChannelModeModifyAck ] GSM48RRChannelModeModifyAck class >> tlvDescription [ ^ OrderedCollection new add: GSM48ChannelDescription asTLVDescription; add: GSM48ChannelMode asTLVDescription; yourself ] ] GSM48SSMessage subclass: GSM48SSFacility [ GSM48SSFacility class >> messageType [ ^ self msgFacility ] GSM48SSFacility class >> tlvDescription [ ^ OrderedCollection new add: GSMFacility asTLVDescription; yourself ] ] GSM48SSMessage subclass: GSM48SSRegister [ GSM48SSRegister class >> messageType [ ^ self msgRegister ] GSM48SSRegister class >> tlvDescription [ ^ OrderedCollection new add: (GSMFacility asTLVDescription beForceTagged; yourself); "MS to mobile can contain this one" add: (GSMSSVersionInd asTLVDescription beOptional; yourself); yourself ] ] GSM48SSMessage subclass: GSM48SSReleaseComplete [ GSM48SSReleaseComplete class >> messageType [ ^ self msgReleaseCompl ] GSM48SSReleaseComplete class >> tlvDescription [ ^ OrderedCollection new add: (GSM48Cause asTLVDescription beOptional; yourself); add: (GSMFacility asTLVDescription beOptional; yourself); yourself ] ] Eval [ GSM48LURequest initialize. GSM48LUReject initialize. GSM48LUAccept initialize. GSM48AuthReq initialize. GSM48AuthResp initialize. GSM48IdentityReq initialize. GSM48IdentityResponse initialize. GSM48CMServiceAccept initialize. GSM48CMServiceReq initialize. GSM48CMServiceReject initialize. GSM48IMSIDetachInd initialize. GSM48TMSIReallocationCommand initialize. GSM48TMSIReallocationComplete initialize. GSM48MMInformation initialize. GSM48CCSetup initialize. GSM48CCCallConfirmed initialize. GSM48CCProceeding initialize. GSM48CCAlerting initialize. GSM48CCConnect initialize. GSM48CCConnectAck initialize. GSM48CCDisconnect initialize. GSM48CCRelease initialize. GSM48CCReleaseCompl initialize. GSM48CCStatus initialize. GSM48CCEmergencySetup initialize. GSM48CCProgress initialize. GSM48RRAssignmentComplete initialize. GSM48RRHandoverCommand initialize. GSM48RRHandoverComplete initialize. GSM48RRHandoverFailure initialize. GSM48RRImmediateAssignCommand initialize. GSM48RRChannelRelease initialize. GSM48RRCipheringModeCommand initialize. GSM48RRCipheringModeComplete initialize. GSM48RRClassmarkChange initialize. GSM48RRPagingResponse initialize. GSM48RRChannelModeModify initialize. GSM48RRChannelModeModifyAck initialize. GSM48SSFacility initialize. GSM48SSRegister initialize. GSM48SSReleaseComplete initialize. "single parts of the IEs" GSMBearerCapOctet3 initialize. GSMBearerCapOctet3a initialize. GSMBearerCapOctet3b initialize. ]