1
0
Fork 0

GSM48: First attempt to create the message...

This commit is contained in:
Holger Hans Peter Freyther 2010-11-18 15:31:25 +01:00
parent fce572c2f2
commit b3181b1eff
1 changed files with 24 additions and 3 deletions

View File

@ -66,8 +66,15 @@ Object subclass: GSM48MIdentity [
imsi: aImsi [ imsi := aImsi. ]
storeOnDirect: aMsg [
imsi ifNotNil: [
^ self storeImsiDirect: aMsg.
].
self notYetImplemented
]
storeImsiDirect: aMsg [
self notYetImplemented.
]
]
@ -78,6 +85,16 @@ IEMessage subclass: GSM48MSG [
Optional := nil.
GSM48MSG class >> mandantory: anArray [
Mandantory := OrderedCollection new.
anArray do: [:each | | name clas meth |
name := each first asString.
clas := each second.
self addInstVarName: name asSymbol.
self compile: '%1 [ ^ %1 ifNil: [%1 := (Smalltalk at: %2) createDefault.]]' % {name. clas}.
Mandantory add: name asSymbol.
]
]
storeOn: aMsg [
@ -87,12 +104,16 @@ IEMessage subclass: GSM48MSG [
"Write all Mandantory parts"
Mandantory ifNotNil: [
Mandantory do: [:each | each storeOnDirect: aMsg ]
Mandantory do: [:each | | tmp |
tmp := self perform: each.
tmp storeOnDirect: aMsg ].
]
"Optional"
Optional ifNotNil: [
Optional do: [:each | each storeOn: aMsg ]
Optional do: [:each | | tmp |
tmp := self perform: each.
tmp storeOnDirect: aMsg ].
]
"TODO: Handle the Conditionals too"
@ -106,7 +127,7 @@ GSM48MSG subclass: GSM48MMMessage [
GSM48MMMessage class >> msgLU [ ^ 8 ]
]
GSM48MSG subclass: LocationUpdatingRequest [
GSM48MMMessage subclass: LocationUpdatingRequest [
<mandantory: #(#(#luType #GSM48KeySeqLuType)
#(#lai #GSM48Lai)
#(#cm1 #GSM48Classmark1)