aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorHolger Hans Peter Freyther <zecke@selfish.org>2010-12-11 12:21:07 +0100
committerHolger Hans Peter Freyther <zecke@selfish.org>2010-12-11 12:21:36 +0100
commit1c8cce66ef7cd750fc48659919daca06eb2e14f0 (patch)
tree71d294f19a4a00ac8bed44e091c9df2dade62b2b
parent421ac8dd46ca48742bcf2f896232faa5dd5424bf (diff)
GSM: Provide simple app to do a LU/Call without feedback.
-rw-r--r--TestPhone.st15
-rw-r--r--WebApp.st157
2 files changed, 97 insertions, 75 deletions
diff --git a/TestPhone.st b/TestPhone.st
index 4057f2c..5e2ef8a 100644
--- a/TestPhone.st
+++ b/TestPhone.st
@@ -104,16 +104,19 @@ Object subclass: IPAConfig [
semaphore [ ^ sem ]
+ doLU: aPhone [
+ ^ LUProcedure initWith: (connection sccpHandler) phone: aPhone.
+ ]
sendLU: aPhone [
- | proc |
- proc := LUProcedure initWith: (connection sccpHandler) phone: aPhone.
- proc execute.
+ (self doLU: aPhone) execute.
+ ]
+
+ doCallNumber: aPhone [
+ ^ CallProcedure initWith: (connection sccpHandler) phone: aPhone.
]
callNumber: aPhone [
- | proc |
- proc := CallProcedure initWith: (connection sccpHandler) phone: aPhone.
- proc execute.
+ ^ (self doCallNumber: aPhone) execute
]
]
diff --git a/WebApp.st b/WebApp.st
index a3e0c1d..2605551 100644
--- a/WebApp.st
+++ b/WebApp.st
@@ -1,4 +1,5 @@
PackageLoader fileInPackage: 'Iliad-Core'.
+PackageLoader fileInPackage: 'Iliad-More-Formula'.
PackageLoader fileInPackage: 'Iliad-Swazoo'.
FileStream fileIn: 'A3A8.st'.
@@ -8,111 +9,128 @@ FileStream fileIn: 'BSSMAP.st'.
FileStream fileIn: 'GSM48.st'.
FileStream fileIn: 'SCCPHandler.st'.
FileStream fileIn: 'GSMDriver.st'.
+FileStream fileIn: 'TestPhone.st'.
Iliad.ILWidget subclass: ServerConfigWidget [
- | app |
-
- ServerConfigWidget class >> initWith: anApp [
- ^ self new
- app: anApp;
- yourself
- ]
-
- app: anApp [
- app := anApp.
- ]
-
contents [
^ [:e |
- e div class: 'server'; build: [:div |
- div h1: 'Server Config'.
- ].
+ 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 [
- | app |
+ configFormOn: anItem [
+ | form |
- PhoneConfigWidget class >> initWith: anApp [
- ^ self new
- app: anApp;
- yourself
+ form := ILFormula on: anItem.
+ (form inputOn: #imsi)
+ labelContents: [:e | e span text: 'IMSI' ].
+ (form inputOn: #auKey)
+ labelContents: [:e | e span text: 'AuKey' ].
+ ^ form
]
- app: anApp [
- app := anApp.
+ 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 div
- class: 'config';
- build: [:div |
- div h1: 'Phone Config'.
- div a
- action: [self connectServer];
- text: 'Connect'.
- ].
+ e a
+ text: 'Start LU';
+ action: [self doLU]
]
]
- connectServer [
+ doLU [
+ | lu |
+ lu := self application gsmServer doLU: self session gsmConfig.
+ lu run.
+ self session procedures add: lu.
]
]
-Iliad.ILWidget subclass: LUWidget [
- | app |
+Object subclass: PhoneNumber [
+ | number |
+ number [ ^ number ]
+ number: aNumber [ number := aNumber ]
+]
- LUWidget class >> initWith: anApp [
- ^ self new
- app: anApp; yourself
+Iliad.ILWidget subclass: CallWidget [
+ createNumberWidget [
+ | form |
+ form := Iliad.ILFormula on: PhoneNumber new.
+ (form inputOn: #number)
+ labelContents: [:e | e span text: 'Number' ].
+ ^ form
]
- app: anApp [
- app := anApp.
+ dial [
+ self lightbox: ((self createNumberWidget)
+ addMessage: [:e | e h2: 'Set the number'];
+ yourself)
+ onAnswer: [:item | item ifNotNil: [
+ self placeCall: item number]]
]
contents [
^ [:e |
- e div
- class: 'lu';
- build: [:div |
- div h1: 'LU Widget'.
- ].
+ e a text: 'Place a call';
+ action: [ self dial ].
]
]
-]
-
-Iliad.ILWidget subclass: CallWidget [
- | app |
- CallWidget class >> initWith: anApp [
- ^ self new
- app: anApp; yourself
+ placeCall: aNumber [
+ | call |
+ call := self application gsmServer doCallNumber: self session gsmConfig.
+ call run.
+ self session procedures add: call.
]
+]
- app: anApp [
- app := anApp.
- ]
+Iliad.ILSession subclass: GSMTestphoneSession [
+ | user gsmConfig procedures |
- contents [
- ^ [:e |
- e div
- class: 'call';
- build: [:div |
- div h1: 'Call Widget'.
- ].
- ]
- ]
+
+ gsmConfig [ ^ gsmConfig ifNil: [gsmConfig := PhoneConfig new. ]]
+ procedures [ ^ procedures ifNil: [procedures := OrderedCollection new]]
]
Iliad.ILApplication subclass: GSMTestphoneApp [
- | config call lu serverConfig gsmServer gsmConfig |
+ | config call lu serverConfig gsmServer |
GSMTestphoneApp class >> path [ ^ 'testphone' ]
- gsmConfig [
- ^ gsmConfig ifNil: [gsmConfig := PhoneConfig new]
+ GSMTestphoneApp class >> initialize [
+ Iliad.ILSessionManager current sessionClass: GSMTestphoneSession.
]
gsmServer [
@@ -120,19 +138,19 @@ Iliad.ILApplication subclass: GSMTestphoneApp [
]
phoneConfig [
- ^ config ifNil: [config := PhoneConfigWidget initWith: self]
+ ^ config ifNil: [config := PhoneConfigWidget new]
]
serverConfig [
- ^ serverConfig ifNil: [serverConfig := ServerConfigWidget initWith: self]
+ ^ serverConfig ifNil: [serverConfig := ServerConfigWidget new]
]
call [
- ^ call ifNil: [call := CallWidget initWith: self]
+ ^ call ifNil: [call := CallWidget new]
]
lu [
- ^ lu ifNil: [lu := LUWidget initWith: self]
+ ^ lu ifNil: [lu := LUWidget new]
]
index [
@@ -147,6 +165,7 @@ Iliad.ILApplication subclass: GSMTestphoneApp [
]
Eval [
+ GSMTestphoneApp initialize.
Iliad.SwazooIliad startOn: 8080.
stdin next.