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

305 lines
7.7 KiB
Smalltalk
Raw Normal View History

2010-12-14 02:03:20 +00:00
"
(C) 2010 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/>.
"
PackageLoader fileInPackage: 'Iliad-Core'.
PackageLoader fileInPackage: 'Iliad-More-Comet'.
PackageLoader fileInPackage: 'Iliad-More-Formula'.
PackageLoader fileInPackage: 'Iliad-Swazoo'.
PackageLoader fileInPackage: 'OsmoGSM'.
FileStream fileIn: 'GSMDriver.st'.
FileStream fileIn: 'TestPhone.st'.
Iliad.ILWidget subclass: ServerConfigWidget [
initialize [
super initialize.
]
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.
]
]
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: ErrorWidget [
| reason |
ErrorWidget class >> initWith: anError [
^ self new
reason: anError;
yourself
]
reason: aReason [
reason := aReason.
]
contents [
^ [:e | e text: reason ]
]
]
Iliad.ILWidget subclass: ProcedureWidget [
runProcedure: aBlock name: aName[
| conn |
[
conn := aBlock value.
conn openConnection.
self session procedures add: conn.
self application procedures markDirty.
] on: Exception do: [:e |
self lightbox: (ErrorWidget initWith: aName, ' could not be started.')
]
]
showStatus: item on: form [
| status |
status := item isComplete
ifTrue: [
item mainProc success
ifTrue: [item mainProc name, ' completed with success']
ifFalse: [item mainProc name, ' completed with failure'].
]
ifFalse: [
item mainProc name, ' in-progress'
].
form text: status.
form button
text: 'Remove';
action: [self markDirty.
item isComplete
ifFalse: [
item sendClearRequest.
].
self session procedures remove: item.].
]
contents [
^ [:e | | procs |
e a
action: [self markDirty];
text: 'Refresh Procedures'.
procs := self session procedures.
procs do: [:each |
e form build: [:form |
self showStatus: each on: form.]
]
]
]
]
ProcedureWidget subclass: IMSIDetachWidget [
contents [
^ [:e |
e a
text: 'Start IMSI Detach';
action: [self doIMSIDetach]
]
]
doIMSIDetach [
self runProcedure: [
self application gsmServer
doIMSIDetach: self session gsmConfig] name: 'IMSI Detach'.
]
]
ProcedureWidget subclass: LUWidget [
contents [
^ [:e |
e a
text: 'Start LU';
action: [self doLU]
]
]
doLU [
self runProcedure: [self application gsmServer doLU: self session gsmConfig] name: 'LU'
]
]
ProcedureWidget subclass: CallWidget [
contents [
^[:e |
e form build: [:form |
form input action: [:val | self placeCall: val].
form button text: 'Call']
]
]
placeCall: aNumber [
self runProcedure: [self application gsmServer doCallNumber: self session gsmConfig nr: aNumber] name: 'Call'
]
]
ProcedureWidget subclass: USSDWidget [
contents [
^[:e |
e form build: [:form |
form input action: [:val | self doUSSD: val].
form button text: 'USSD']
]
]
doUSSD: aNumber [
self runProcedure: [self application gsmServer doUSSD: self session gsmConfig nr: aNumber] name: 'USSD'.
]
]
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 procedureWidget ussd imsiDetach |
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]
]
procedures [
^ procedureWidget ifNil: [procedureWidget := ProcedureWidget new]
]
call [
^ call ifNil: [call := CallWidget new]
]
imsiDetach [
^ imsiDetach ifNil: [imsiDetach := IMSIDetachWidget new].
]
lu [
^ lu ifNil: [lu := LUWidget new]
]
ussd [
^ ussd ifNil: [ussd := USSDWidget new]
]
index [
<category: 'controllers'>
^ [:e |
e
build: self cometConnection;
build: self serverConfig;
build: self phoneConfig;
build: self imsiDetach;
build: self lu;
build: self call;
build: self ussd;
build: self procedures.
].
]
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.
]