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

sccp: Move the state transition into a central place

This commit is contained in:
Holger Hans Peter Freyther 2011-06-20 11:14:49 +02:00
parent bd2acafc8e
commit eda5c4bd08
1 changed files with 29 additions and 16 deletions

View File

@ -88,37 +88,49 @@ Object subclass: SCCPConnectionBase [
^ dst
]
changeState: newState do: aBlock [
state := newState.
aBlock value.
]
connectionRequest: aData [
| res |
<category: 'handling'>
"Send the confirmation now"
state := self class stateRequested.
res := Osmo.SCCPConnectionRequest
self changeState: self class stateRequested do: [
res := Osmo.SCCPConnectionRequest
initWith: (self srcRef) dest: (Osmo.SCCPAddress createWith: 254) data: aData.
self nextPut: res toMessage.
self nextPut: res toMessage.
].
]
confirm: aCC [
<category: 'handling'>
self dstRef: aCC src.
state := self class stateConnected.
confirmSem signal.
self changeState: self class stateConnected do: [
self dstRef: aCC src.
confirmSem signal.
]
]
release [
| rlsd |
<category: 'handling'>
state := self class stateReleased.
rlsd := Osmo.SCCPConnectionReleased initWithDst: self dstRef src: self srcRef cause: 0.
self nextPut: rlsd toMessage.
self changeState: self class stateReleased do: [
rlsd := Osmo.SCCPConnectionReleased initWithDst: self dstRef src: self srcRef cause: 0.
self nextPut: rlsd toMessage.
]
]
releaseComplete: aMSG [
<category: 'handling'>
"TODO: verify that we are in the right state"
state := self class stateReleaseComplete.
self terminate.
self changeState: self class stateReleaseComplete do: [
self terminate.
]
]
released: aRLSD [
@ -126,11 +138,12 @@ Object subclass: SCCPConnectionBase [
<category: 'handling'>
"Give up local resources here. We are done."
state := self class stateReleaseComplete.
rlc := Osmo.SCCPConnectionReleaseComplete
initWithDst: aRLSD src src: aRLSD dst.
self nextPut: rlc toMessage.
self terminate.
self changeState: self class stateReleaseComplete do: [
rlc := Osmo.SCCPConnectionReleaseComplete
initWithDst: aRLSD src src: aRLSD dst.
self nextPut: rlc toMessage.
self terminate.
]
]
nextPutData: aMsg [