1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-testphone/WebApp.st

201 lines
4.7 KiB
Smalltalk
Raw Normal View History

PackageLoader fileInPackage: 'Iliad-Core'.
PackageLoader fileInPackage: 'Iliad-More-Formula'.
PackageLoader fileInPackage: 'Iliad-Swazoo'.
FileStream fileIn: 'A3A8.st'.
FileStream fileIn: 'Messages.st'.
FileStream fileIn: 'BSSAP.st'.
FileStream fileIn: 'BSSMAP.st'.
FileStream fileIn: 'GSM48.st'.
FileStream fileIn: 'SCCPHandler.st'.
FileStream fileIn: 'GSMDriver.st'.
FileStream fileIn: 'TestPhone.st'.
Iliad.ILWidget subclass: ServerConfigWidget [
contents [
^ [:e |
self application gsmServer isConnected
ifTrue: [
e text: 'The A link is connected to the MSC'.
]
ifFalse: [
e text: 'The A link is not connected: '.
e a
text: 'Connect';
action: [self connectServer]
].
]
]
connectServer [
(self application gsmServer)
connect;
serve.
[
(Delay forSeconds: 5) wait.
self send: #markDirty.
] fork.
]
]
Iliad.ILWidget subclass: PhoneConfigWidget [
configFormOn: anItem [
| form |
form := ILFormula on: anItem.
(form inputOn: #imsi)
labelContents: [:e | e span text: 'IMSI' ].
(form inputOn: #auKey)
labelContents: [:e | e span text: 'AuKey' ].
^ form
]
configurePhone [
self lightbox: ((self configFormOn: self session gsmConfig)
addMessage: [:e | e h2: 'Configure Test Phone'];
yourself)
]
contents [
^ [:e | e a text: 'Configure phone'; action: [self configurePhone]].
]
]
Iliad.ILWidget subclass: LUWidget [
contents [
^ [:e |
e a
text: 'Start LU';
action: [self doLU]
]
]
doLU [
| lu |
lu := self application gsmServer doLU: self session gsmConfig.
lu run.
self session procedures add: lu.
]
]
Object subclass: PhoneNumber [
| number |
number [ ^ number ]
number: aNumber [ number := aNumber ]
]
Iliad.ILWidget subclass: CallWidget [
createNumberWidget [
| form |
form := Iliad.ILFormula on: PhoneNumber new.
(form inputOn: #number)
labelContents: [:e | e span text: 'Number' ].
^ form
]
dial [
self lightbox: ((self createNumberWidget)
addMessage: [:e | e h2: 'Set the number'];
yourself)
onAnswer: [:item | item ifNotNil: [
self placeCall: item number]]
]
contents [
^ [:e |
e a text: 'Place a call';
action: [ self dial ].
]
]
placeCall: aNumber [
| call |
call := self application gsmServer doCallNumber: self session gsmConfig.
call run.
self session procedures add: call.
]
]
Iliad.ILSession subclass: GSMTestphoneSession [
| user gsmConfig procedures |
2010-12-11 11:30:46 +00:00
isAuthenticated [
^ user = 'toto-user'
]
username: aUser [
user := aUser.
]
gsmConfig [ ^ gsmConfig ifNil: [gsmConfig := PhoneConfig new. ]]
procedures [ ^ procedures ifNil: [procedures := OrderedCollection new]]
]
Iliad.ILApplication subclass: GSMTestphoneApp [
| config call lu serverConfig gsmServer |
GSMTestphoneApp class >> path [ ^ 'testphone' ]
GSMTestphoneApp class >> initialize [
Iliad.ILSessionManager current sessionClass: GSMTestphoneSession.
]
gsmServer [
^ gsmServer ifNil: [gsmServer := IPAConfig new]
]
phoneConfig [
^ config ifNil: [config := PhoneConfigWidget new]
]
serverConfig [
^ serverConfig ifNil: [serverConfig := ServerConfigWidget new]
]
call [
^ call ifNil: [call := CallWidget new]
]
lu [
^ lu ifNil: [lu := LUWidget new]
]
index [
<category: 'controllers'>
^ [:e |
e build: self serverConfig.
e build: self phoneConfig.
e build: self call.
e build: self lu.
].
]
2010-12-11 11:30:46 +00:00
loginContents [
<category: 'building'>
^[:e |
e form build: [:form |
form input action: [:val | self login: val].
form button text: 'Login']]
]
login: aString [
<category: 'actions'>
self session username: aString.
self redirectToCurrentController
]
dispatchOverride [
<category: 'dispatching'>
^self session isAuthenticated
ifFalse: [self loginContents]
ifTrue: [super dispatchOverride]
]
]
Eval [
GSMTestphoneApp initialize.
Iliad.SwazooIliad startOn: 8080.
stdin next.
]