PackageLoader fileInPackage: 'Iliad-Core'. PackageLoader fileInPackage: 'Iliad-More-Comet'. 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.ILCometEvent subclass: PhoneRefresh [ ] Iliad.ILWidget subclass: ServerConfigWidget [ initialize [ super initialize. self subscribeToCometEvent: PhoneRefresh. ] 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 [ | context | (self application gsmServer) connect; serve. context := self context. [ ILCurrentContext processVariable value: context. (Delay forSeconds: 5) wait. self session cometHandler handleEvent: PhoneRefresh new. ] 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: 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[ | proc | [ proc := aBlock value. proc run. self session procedures add: proc. self application procedures markDirty. ] on: Exception do: [:e | self lightbox: (ErrorWidget initWith: aName, ' could not be started.') ] ] ] 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' ] ] Iliad.ILWidget subclass: ProcedureWidget [ showStatus: item on: form [ | status | status := item complete ifTrue: [ item success ifTrue: [item name, ' completed with success'] ifFalse: [item name, ' completed with failure']. ] ifFalse: [ item name, ' in-progress' ]. form text: status. form button text: 'Remove'; action: [self markDirty. 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.] ] ] ] ] Iliad.ILSession subclass: GSMTestphoneSession [ | user gsmConfig procedures | 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 | 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] ] lu [ ^ lu ifNil: [lu := LUWidget new] ] index [ ^ [:e | e build: self cometConnection; build: self serverConfig; build: self phoneConfig; build: self lu; build: self call; build: self procedures. ]. ] loginContents [ ^[:e | e form build: [:form | form input action: [:val | self login: val]. form button text: 'Login']] ] login: aString [ self session username: aString. self redirectToCurrentController ] dispatchOverride [ ^self session isAuthenticated ifFalse: [self loginContents] ifTrue: [super dispatchOverride] ] ] Eval [ GSMTestphoneApp initialize. Iliad.SwazooIliad startOn: 8080. stdin next. ]