1
0
Fork 0

m2ua: Begin with a M2UA AS and ASP state machine and support code

This commit is contained in:
Holger Hans Peter Freyther 2013-04-08 08:40:20 +02:00
parent 009957dffc
commit 12bdaf75f6
3 changed files with 263 additions and 1 deletions

View File

@ -11,11 +11,15 @@ CONVERT_RULES = -r'Osmo.LogManager->LogManager' \
-r'(Duration milliseconds: ``@args1) -> (Duration milliSeconds: ``@args1)' \
-r'PP.PPCompositeParser->PPCompositeParser' \
-r'PP.PPCompositeParserTest->PPCompositeParserTest' \
-r'STInST.RBProgramNodeVisitor->RBProgramNodeVisitor' \
-r'STInST.RBBracketedMethodParser->RBParser' \
-r'Osmo.MessageBuffer->MessageBuffer' \
-r'SystemExceptions.NotFound->NotFound' \
-r'(``@object substrings: ``@args1)->(``@object subStrings: ``@args1)' \
-r'(Dictionary from: ``@args1)->(Dictionary newFrom: ``@args1)' \
-r'(``@object copyFrom: ``@args1)->(``@object copyFrom: ``@args1 to: ``@object size)' \
-r'(``@object nl)->(``@object cr; lf)' \
-r'(``@object methodSourceString)->(``@object sourceCode)' \
-C -IPAGSTTests
# Can not be parsed right now..
@ -36,7 +40,7 @@ ISUP = \
isup/ISUPTests.st
UA = \
ua/M2UA.st
ua/M2UA.st ua/M2UAStates.st
OSMO = \
osmo/LogAreaOsmo.st \

View File

@ -6,6 +6,7 @@
<prereq>OsmoCore</prereq>
<prereq>PetitParser</prereq>
<prereq>Sockets</prereq>
<prereq>Parser</prereq>
<filein>core/Extensions.st</filein>
<filein>core/MessageStructure.st</filein>
@ -25,6 +26,7 @@
<filein>sccp/SCCPAddress.st</filein>
<filein>mtp3/MTP3Messages.st</filein>
<filein>ua/M2UA.st</filein>
<filein>ua/M2UAStates.st</filein>
<filein>osmo/LogAreaOsmo.st</filein>
<filein>osmo/OsmoUDPSocket.st</filein>
<filein>osmo/OsmoCtrlLogging.st</filein>

256
ua/M2UAStates.st Normal file
View File

@ -0,0 +1,256 @@
"
(C) 2013 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/>.
"
STInST.RBProgramNodeVisitor subclass: M2UAStateMachineVisitor [
| states |
<comment: nil>
<category: 'OsmoNetwork-M2UA-States'>
acceptMessageNode: aNode [
aNode selector = #moveToState:
ifTrue: [self addTransition: aNode arguments first name asString].
super acceptMessageNode: aNode
]
addTransition: aStateName [
<category: 'states'>
self stateSet add: aStateName
]
stateSet [
<category: 'states'>
^states ifNil: [states := Set new]
]
]
Object subclass: M2UAStateBase [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
M2UAStateBase class >> addStateFrom: aMethod to: newState class: aClass on: aStream [
aStream
nextPutAll: aClass name asString;
nextPutAll: ' -> ';
nextPutAll: newState;
nextPutAll: ' [ label = "';
nextPutAll: aMethod asString allButLast;
nextPutAll: '"];';
nl.
]
M2UAStateBase class >> generateGraphviz [
| stream |
stream := WriteStream on: String new.
stream
nextPutAll: 'digraph {';
nl.
self subclassesDo:
[:class |
class selectors do: [:selector |
| codeVisitor method |
method := class >> selector.
codeVisitor := (STInST.RBBracketedMethodParser
parseMethod: method methodSourceString) body
acceptVisitor: M2UAStateMachineVisitor new.
codeVisitor stateSet do:
[:newState |
self
addStateFrom: method selector asString
to: newState
class: class
on: stream]]].
^stream
nextPutAll: '}';
contents
]
]
M2UAStateBase subclass: M2UAAsState [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
]
M2UAAsState subclass: M2UAAsStateInactive [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
onAllAspDown: anEvent [
"All ASP trans to ASP-DOWN"
<category: 'state-changes'>
self moveToState: M2UAAsStateDown
]
onAspActive: anEvent [
"one ASP trans to ACTIVE"
<category: 'state-changes'>
self moveToState: M2UAAsStateActive
]
]
M2UAAsState subclass: M2UAAsStatePending [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
onAspUp: anEvent [
"One ASP trans to ASP-ACTIVE"
<category: 'state-change'>
self stopTr.
self moveToState: M2UAAsStateActive
]
onTrExpiry [
"Tr Expiry, at least one ASP in ASP-INACTIVE -> AS-INACTIVE"
"Tr Expiry and no ASPin ASP-INACTIVE state"
<category: 'state-change'>
self hasInactiveAsp
ifTrue: [self moveToState: M2UAAsStateInactive]
ifFalse: [self moveToState: M2UAAsStateDown]
]
]
M2UAStateBase subclass: M2UAAspState [
<category: 'OsmoNetwork-M2UA-States'>
<comment: 'I am the base class of the ASP State Machine from RFC 3331 on Page 61.'>
]
M2UAAspState subclass: M2UAAspStateActive [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
onAspDown: anEvent [
<category: 'state-changes'>
self moveToState: M2UAAspStateDown
]
onAspInactive: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateInactive
]
onOtherAspInAsOverrides: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateInactive
]
onSctpCdi: anEvent [
<category: 'state-changes'>
self moveToState: M2UAAspStateDown
]
onSctpRi: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateDown
]
]
M2UAAspState subclass: M2UAAspStateDown [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
onAspUp: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateInactive
]
]
M2UAAspState subclass: M2UAAspStateInactive [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
onAspActive: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateActive
]
onAspDown: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateDown
]
onSctpCdi: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateDown
]
onSctpRi: anEvent [
<category: 'state-changes'>
^self moveToState: M2UAAspStateDown
]
]
M2UAAsState subclass: M2UAAsStateDown [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
onAspInactive: anEvent [
"One ASP trans to ASP-INACTIVE"
<category: 'state-changes'>
self movesToState: M2UAAsStateInactive
]
]
M2UAAsState subclass: M2UAAsStateActive [
<category: 'OsmoNetwork-M2UA-States'>
<comment: nil>
onLastActiveAspDown: anEvent [
"Last ACTIVEASP trans to ASP-INACTIVE or ASP-Down"
<category: 'state-changes'>
self startTr.
self moveToState: M2UAAsStatePending
]
]