smalltalk
/
osmo-st-gsm
Archived
1
0
Fork 0

typo: Mandantory -> Mandatory (common typo of mine)

This commit is contained in:
Holger Hans Peter Freyther 2012-08-03 11:00:08 +02:00
parent 5c290fc82c
commit 2e60faeacc
1 changed files with 105 additions and 105 deletions

210
GSM48.st
View File

@ -1197,7 +1197,7 @@ IEMessage subclass: GSM48MSG [
| seq ti |
<category: 'OsmoGSM'>
<comment: 'GSM48 has helper code for mandantory types'>
<comment: 'GSM48 has helper code for mandatory types'>
GSM48MSG class >> addVariable: aName [
"Check if the variable exists, otherwise add it"
@ -1207,18 +1207,18 @@ IEMessage subclass: GSM48MSG [
].
]
GSM48MSG class >> addMandantory: aName with: aClass [
GSM48MSG class >> addMandatory: aName with: aClass [
<comment: 'creation'>
self addVariable: aName asSymbol.
self compile: '%1 [ ^ %1 ifNil: [%1 := %2 createDefault.]]' % {aName. aClass}.
self Mandantory add: ({aName asSymbol. #normal} -> aClass).
self Mandatory add: ({aName asSymbol. #normal} -> aClass).
]
GSM48MSG class >> addTaggedMandantory: aName with: aClass [
GSM48MSG class >> addTaggedMandatory: aName with: aClass [
<comment: 'creation'>
self addVariable: aName asSymbol.
self compile: '%1 [ ^ %1 ifNil: [%1 := %2 createDefault.]]' % {aName. aClass}.
self Mandantory add: ({aName asSymbol. #tagged} -> aClass).
self Mandatory add: ({aName asSymbol. #tagged} -> aClass).
]
GSM48MSG class >> addOptional: aName with: aClass [
@ -1271,8 +1271,8 @@ IEMessage subclass: GSM48MSG [
res seq: (aStream next bitShift: -6).
"This is messy. The GSM04.80 spec had the great idea of adding
tagged mandantory items and we need to deal with it here."
self Mandantory do: [:tuple |
tagged mandatory items and we need to deal with it here."
self Mandatory do: [:tuple |
| len name type clazz |
name := tuple key first.
type := tuple key second.
@ -1280,7 +1280,7 @@ IEMessage subclass: GSM48MSG [
type = #tagged ifTrue: [
aStream next = clazz elementId ifFalse: [
^ self error: 'Mandantory Tagged Element %1 not present.' % {name->clazz}.
^ self error: 'Mandatory Tagged Element %1 not present.' % {name->clazz}.
].
].
@ -1343,8 +1343,8 @@ IEMessage subclass: GSM48MSG [
aMsg putByte: classType.
aMsg putByte: type.
"Write all Mandantory parts"
self class Mandantory do: [:tuple | | tmp |
"Write all Mandatory parts"
self class Mandatory do: [:tuple | | tmp |
tmp := self perform: tuple key first.
tuple key second = #tagged
ifTrue: [tmp writeOn: aMsg.]
@ -1530,13 +1530,13 @@ GSM48MSG subclass: GSM48SSMessage [
GSM48MMMessage subclass: GSM48LURequest [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
Optional := nil.
GSM48LURequest class >> messageType [ ^ self msgLUReq ]
GSM48LURequest class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
GSM48LURequest class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ].
]
GSM48LURequest class >> Optional [
@ -1544,21 +1544,21 @@ GSM48MMMessage subclass: GSM48LURequest [
]
GSM48LURequest class >> initialize [
self addMandantory: 'luType' with: GSM48KeySeqLuType.
self addMandantory: 'lai' with: GSM48Lai.
self addMandantory: 'cm1' with: GSM48Classmark1.
self addMandantory: 'mi' with: GSM48MIdentity.
self addMandatory: 'luType' with: GSM48KeySeqLuType.
self addMandatory: 'lai' with: GSM48Lai.
self addMandatory: 'cm1' with: GSM48Classmark1.
self addMandatory: 'mi' with: GSM48MIdentity.
]
]
GSM48MMMessage subclass: GSM48LUAccept [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
Optional := nil.
GSM48LUAccept class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
GSM48LUAccept class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ].
]
GSM48LUAccept class >> Optional [
@ -1567,7 +1567,7 @@ GSM48MMMessage subclass: GSM48LUAccept [
GSM48LUAccept class >> messageType [ ^ self msgLUAcc ]
GSM48LUAccept class >> initialize [
self addMandantory: 'cause' with: GSM48Lai.
self addMandatory: 'cause' with: GSM48Lai.
self addOptional: 'mi' with: GSM48MIdentity.
self addOptional: 'follow' with: GSM48FollowOn.
self addOptional: 'cts' with: GSM48CTSPermission.
@ -1577,110 +1577,110 @@ GSM48MMMessage subclass: GSM48LUAccept [
GSM48MMMessage subclass: GSM48LUReject [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
Optional := nil.
GSM48LUReject class >> messageType [ ^ self msgLURej ]
GSM48LUReject class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
GSM48LUReject class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ].
]
GSM48LUReject class >> initialize [
self addMandantory: 'cause' with: GSM48RejectCause.
self addMandatory: 'cause' with: GSM48RejectCause.
]
]
GSM48MMMessage subclass: GSM48AuthRej [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
Optional := nil.
GSM48AuthRej class >> messageType [ ^ self msgAuRej ]
GSM48AuthRej class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
GSM48AuthRej class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ].
]
]
GSM48MMMessage subclass: GSM48AuthReq [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
Optional := nil.
GSM48AuthReq class >> messageType [ ^ self msgAuReq ]
GSM48AuthReq class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
GSM48AuthReq class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ].
]
GSM48AuthReq class >> initialize [
self addMandantory: 'key' with: GSM48KeySeqLuType.
self addMandantory: 'auth' with: GSM48AuthRand.
self addMandatory: 'key' with: GSM48KeySeqLuType.
self addMandatory: 'auth' with: GSM48AuthRand.
]
]
GSM48MMMessage subclass: GSM48AuthResp [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
GSM48AuthResp class >> messageType [ ^ self msgAuRes ]
GSM48AuthResp class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
GSM48AuthResp class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ].
]
GSM48AuthResp class >> initialize [
self addMandantory: 'sres' with: GSM48AuthSRES.
self addMandatory: 'sres' with: GSM48AuthSRES.
]
]
GSM48MMMessage subclass: GSM48IdentityReq [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
GSM48IdentityReq class >> messageType [ ^ self msgIdReq ]
GSM48IdentityReq class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
GSM48IdentityReq class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ].
]
GSM48IdentityReq class >> initialize [
self addMandantory: 'idType' with: GSM48IdentityType.
self addMandatory: 'idType' with: GSM48IdentityType.
]
]
GSM48MMMessage subclass: GSM48IdentityResponse [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
GSM48IdentityResponse class >> messageType [ ^ self msgIdRes ]
GSM48IdentityResponse class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
GSM48IdentityResponse class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ].
]
GSM48IdentityResponse class >> initialize [
self addMandantory: 'mi' with: GSM48MIdentity.
self addMandatory: 'mi' with: GSM48MIdentity.
]
]
GSM48MMMessage subclass: GSM48CMServiceReq [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
Optional := nil.
GSM48CMServiceReq class >> messageType [ ^ self msgCMReq ]
GSM48CMServiceReq class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
GSM48CMServiceReq class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ].
]
GSM48CMServiceReq class >> Optional [
^ Optional ifNil: [ Optional := OrderedCollection new ]
]
GSM48CMServiceReq class >> initialize [
self addMandantory: 'keyAndType' with: GSM48KeySeqLuType.
self addMandantory: 'cm2' with: GSM48Classmark2.
self addMandantory: 'mi' with: GSM48MIdentity.
self addMandatory: 'keyAndType' with: GSM48KeySeqLuType.
self addMandatory: 'cm2' with: GSM48Classmark2.
self addMandatory: 'mi' with: GSM48MIdentity.
self addOptional: 'prio' with: GSMPriorityLevel.
]
@ -1690,41 +1690,41 @@ GSM48MMMessage subclass: GSM48CMServiceReq [
GSM48MMMessage subclass: GSM48CMServiceReject [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
GSM48CMServiceReject class >> messageType [ ^ self msgCMReject ]
GSM48CMServiceReject class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]
GSM48CMServiceReject class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ]
]
GSM48CMServiceReject class >> initialize [
self addMandantory: 'reject' with: GSM48RejectCause.
self addMandatory: 'reject' with: GSM48RejectCause.
]
]
GSM48MMMessage subclass: GSM48IMSIDetachInd [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
GSM48IMSIDetachInd class >> messageType [ ^ self msgIMSIDetach ]
GSM48IMSIDetachInd class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
GSM48IMSIDetachInd class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ].
]
GSM48IMSIDetachInd class >> initialize [
self addMandantory: 'cm1' with: GSM48Classmark1.
self addMandantory: 'mi' with: GSM48MIdentity.
self addMandatory: 'cm1' with: GSM48Classmark1.
self addMandatory: 'mi' with: GSM48MIdentity.
]
]
GSM48CCMessage subclass: GSM48CCSetup [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
Optional := nil.
GSM48CCSetup class >> messageType [ ^ self msgSetup ]
GSM48CCSetup class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ].
GSM48CCSetup class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ].
]
GSM48CCSetup class >> Optional [
^ Optional ifNil: [ Optional := OrderedCollection new ]
@ -1803,12 +1803,12 @@ GSM48CCMessage subclass: GSM48CCSetup [
GSM48CCMessage subclass: GSM48CCProceeding [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
Optional := nil.
GSM48CCProceeding class >> messageType [ ^ self msgProceeding ]
GSM48CCProceeding class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]
GSM48CCProceeding class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ]
]
GSM48CCProceeding class >> Optional [
^ Optional ifNil: [ Optional := OrderedCollection new ]
@ -1840,12 +1840,12 @@ GSM48CCMessage subclass: GSM48CCProceeding [
GSM48CCMessage subclass: GSM48CCAlerting [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
Optional := nil.
GSM48CCAlerting class >> messageType [ ^ self msgAlerting ]
GSM48CCAlerting class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]
GSM48CCAlerting class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ]
]
GSM48CCAlerting class >> Optional [
@ -1865,12 +1865,12 @@ GSM48CCMessage subclass: GSM48CCAlerting [
GSM48CCMessage subclass: GSM48CCConnect [
<category: 'OsmoGSM'>
Mandantory := nil.
Mandatory := nil.
Optional := nil.
GSM48CCConnect class >> messageType [ ^ self msgConnect ]
GSM48CCConnect class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new. ]
GSM48CCConnect class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new. ]
]
GSM48CCConnect class >> Optional [
@ -1892,11 +1892,11 @@ GSM48CCMessage subclass: GSM48CCConnectAck [
<category: 'OsmoGSM'>
Optional := nil.
Mandantory := nil.
Mandatory := nil.
GSM48CCConnectAck class >> messageType [ ^ self msgConnectAck ]
GSM48CCConnectAck class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new. ]
GSM48CCConnectAck class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new. ]
]
GSM48CCConnectAck class >> Optional [
@ -1911,11 +1911,11 @@ GSM48CCMessage subclass: GSM48CCDisconnect [
<category: 'OsmoGSM'>
Optional := nil.
Mandantory := nil.
Mandatory := nil.
GSM48CCDisconnect class >> messageType [ ^ self msgDisconnect ]
GSM48CCDisconnect class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new. ]
GSM48CCDisconnect class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new. ]
]
GSM48CCDisconnect class >> Optional [
@ -1923,7 +1923,7 @@ GSM48CCMessage subclass: GSM48CCDisconnect [
]
GSM48CCDisconnect class >> initialize [
self addMandantory: 'cause' with: GSM48Cause.
self addMandatory: 'cause' with: GSM48Cause.
self addOptional: 'facility' with: GSMFacility.
self addOptional: 'progress' with: GSMProgress.
self addOptional: 'useruser' with: GSMUserUser.
@ -1939,11 +1939,11 @@ GSM48CCMessage subclass: GSM48CCRelease [
<category: 'OsmoGSM'>
Optional := nil.
Mandantory := nil.
Mandatory := nil.
GSM48CCRelease class >> messageType [ ^ self msgRelease ]
GSM48CCRelease class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]
GSM48CCRelease class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ]
]
GSM48CCRelease class >> Optional [
@ -1963,11 +1963,11 @@ GSM48CCMessage subclass: GSM48CCReleaseCompl [
<category: 'OsmoGSM'>
Optional := nil.
Mandantory := nil.
Mandatory := nil.
GSM48CCReleaseCompl class >> messageType [ ^ self msgReleaseCompl ]
GSM48CCReleaseCompl class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]
GSM48CCReleaseCompl class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ]
]
GSM48CCReleaseCompl class >> Optional [
@ -1986,11 +1986,11 @@ GSM48CCMessage subclass: GSM48CCStatus [
<category: 'OsmoGSM'>
Optional := nil.
Mandantory := nil.
Mandatory := nil.
GSM48CCStatus class >> messageType [ ^ self msgStatus ]
GSM48CCStatus class >> Mandantory [
^ Mandantory ifNil: [Mandantory := OrderedCollection new]
GSM48CCStatus class >> Mandatory [
^ Mandatory ifNil: [Mandatory := OrderedCollection new]
]
GSM48CCStatus class >> Optional [
@ -1998,8 +1998,8 @@ GSM48CCMessage subclass: GSM48CCStatus [
]
GSM48CCStatus class >> initialize [
self addMandantory: 'cause' with: GSM48Cause.
self addMandantory: 'callState' with: GSM48Callstate.
self addMandatory: 'cause' with: GSM48Cause.
self addMandatory: 'callState' with: GSM48Callstate.
self addOptional: 'auxStates' with: GSM48AuxillaryStates.
]
]
@ -2008,15 +2008,15 @@ GSM48RRMessage subclass: GSM48RRAssignmentComplete [
<category: 'OsmoGSM'>
Optional := nil.
Mandantory := nil.
Mandatory := nil.
GSM48RRAssignmentComplete class >> messageType [
<category: 'factory'>
^ self msgAssignmentComplete
]
GSM48RRAssignmentComplete class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]
GSM48RRAssignmentComplete class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ]
]
GSM48RRAssignmentComplete class >> Optional [
@ -2024,7 +2024,7 @@ GSM48RRMessage subclass: GSM48RRAssignmentComplete [
]
GSM48RRAssignmentComplete class >> initialize [
self addMandantory: 'cause' with: GSMRRCause.
self addMandatory: 'cause' with: GSMRRCause.
]
]
@ -2032,11 +2032,11 @@ GSM48SSMessage subclass: GSM48SSFacility [
<category: 'OsmoGSM'>
Optional := nil.
Mandantory := nil.
Mandatory := nil.
GSM48SSFacility class >> messageType [ ^ self msgFacility ]
GSM48SSFacility class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]
GSM48SSFacility class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ]
]
GSM48SSFacility class >> Optional [
@ -2044,7 +2044,7 @@ GSM48SSMessage subclass: GSM48SSFacility [
]
GSM48SSFacility class >> initialize [
self addMandantory: 'facility' with: GSMFacility.
self addMandatory: 'facility' with: GSMFacility.
]
]
@ -2052,11 +2052,11 @@ GSM48SSMessage subclass: GSM48SSRegister [
<category: 'OsmoGSM'>
Optional := nil.
Mandantory := nil.
Mandatory := nil.
GSM48SSRegister class >> messageType [ ^ self msgRegister ]
GSM48SSRegister class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]
GSM48SSRegister class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ]
]
@ -2065,7 +2065,7 @@ GSM48SSMessage subclass: GSM48SSRegister [
]
GSM48SSRegister class >> initialize [
self addTaggedMandantory: 'facility' with: GSMFacility.
self addTaggedMandatory: 'facility' with: GSMFacility.
"MS to mobile can contain this one"
self addOptional: 'ssVersion' with: GSMSSVersionInd.
@ -2076,11 +2076,11 @@ GSM48SSMessage subclass: GSM48SSReleaseComplete [
<category: 'OsmoGSM'>
Optional := nil.
Mandantory := nil.
Mandatory := nil.
GSM48SSReleaseComplete class >> messageType [ ^ self msgReleaseCompl ]
GSM48SSReleaseComplete class >> Mandantory [
^ Mandantory ifNil: [ Mandantory := OrderedCollection new ]
GSM48SSReleaseComplete class >> Mandatory [
^ Mandatory ifNil: [ Mandatory := OrderedCollection new ]
]
GSM48SSReleaseComplete class >> Optional [