DIRECTORY IO, Commander USING [ CommandProc, Register ], Convert USING [ RopeFromInt ], Lark USING [ bStar, bThorp, ConnectionSpec, CommandEvent, CommandEvents, CommandEventSequence, Device, disabled, EchoParameters, EchoParameterRecord, enabled, endNum, Event, KeyTable, Milliseconds, o3i1, o2i2, o1i1, Passel, reset, SHHH, StatusEvent, Tone, ToneSpec, ToneSpecRec ], LarkPlay USING [ ToneList, ToneSpec, ToneSpecRec ], LarkRpcControl, LarkSmarts, List USING [ Nconc1 ], Log USING [ ProblemFR, Report ], Nice, Process USING [ Detach, EnableAborts, MsecToTicks, SetTimeout ], Rope USING [ Cat, Concat, Fetch, Length, ROPE, Substr, Translate, TranslatorType ], RPC USING [ CallFailed ], ThNet USING [ pd ], ThPartyPrivate USING [ SmartsData ], Thrush USING[ H, pERROR, ProseSpec, ProseSpecs, ROPE, SHHH, SmartsHandle, ThHandle ], ThSmartsPrivate USING [ ConvDesc, flushMarker, GetConvDesc, HookState, proseFailure, indexMarkerEnd, LarkInfo, LarkProseQueue, LarkState, LarkStateSpec, LSwitches, LState, maxClientMarker, maxControlMarker, ProgressTones, ProseCmd, SmartsInfo, TerminalType ], TU USING [ RefAddr ] ; LarkOutImpl: CEDAR MONITOR LOCKS info USING info: LarkInfo IMPORTS Commander, Convert, IO, LarkRpcControl, List, Log, Nice, Process, Rope, RPC, ThNet, Thrush, ThSmartsPrivate, TU EXPORTS ThSmartsPrivate= { OPEN IO; ConvDesc: TYPE = ThSmartsPrivate.ConvDesc; H: PROC[r: REF] RETURNS[Thrush.ThHandle] = INLINE {RETURN[Thrush.H[r]]; }; LarkInfo: TYPE = ThSmartsPrivate.LarkInfo; LarkState: TYPE = ThSmartsPrivate.LarkState; SmartsData: TYPE = ThPartyPrivate.SmartsData; SmartsInfo: TYPE = ThSmartsPrivate.SmartsInfo; SmartsHandle: TYPE = Thrush.SmartsHandle; TerminalType: TYPE = ThSmartsPrivate.TerminalType; ProseCmd: TYPE = ThSmartsPrivate.ProseCmd; ROPE: TYPE = Thrush.ROPE; firstTone: LarkState = FIRST[ThSmartsPrivate.ProgressTones]; bStar: Lark.Event = Lark.bStar; bThorp: Lark.Event = Lark.bThorp; enabled: Lark.Event = Lark.enabled; endNum: Lark.Event = Lark.endNum; disabled: Lark.Event = Lark.disabled; reset: Lark.Event = Lark.reset; larkRegistry: ROPE _ ".Lark"; PD: TYPE = RECORD [ waitForTelco: CARDINAL _ 500, telcoMinOn: CARDINAL _ 60, telcoMinOff: CARDINAL _ 60, flashWaitTime: CARDINAL _ 800, idleWaitTime: CARDINAL _ 20000, -- time for supervisor to wait for more events. backDoorOH: BOOL_FALSE, callTimeoutOK: BOOL_FALSE, -- set to keep Thrush alive when debugging a Lark. tonesInvalid: BOOL_TRUE, tonesLast: BOOL_TRUE -- sets up alternate lark setup situation in supervisor loop ]; pd: REF PD _ NEW[PD_[]]; dialTone: LarkPlay.ToneSpec _ NIL; busyTone: LarkPlay.ToneSpec _ NIL; errorTone: LarkPlay.ToneSpec _ NIL; ringbackTone: LarkPlay.ToneSpec _ NIL; quenchSpec: Lark.ToneSpec _ NEW[Lark.ToneSpecRec _[volume: 0, totalTime: 0, tones: LIST[[0,0,0,0]]]]; pReset: PUBLIC ProseCmd _ "c"; --  is ESC stopAndFlush: PUBLIC ProseCmd _ "P0;10z\\"; commenceSpeech: ProseCmd = "P0;11z\\"; cmdLeader: ProseCmd = "P0;21;"; -- for constructing arbitrary commands; rename to indexMarkerStart indexMarkerLen: INT = 13; indexMarkerEnd: ProseCmd = "z\\"; maxTextPktLen: INT _ 90; maxPkts: INT = 250 / maxTextPktLen; -- Prose can hold `several hundred' chars numPkts: INT _ 3; minClientMarker: INT = 1; minControlMarker: INT = 200; -- reserved for packet control speechDoneMarker: INT = 255; speechDone: ProseCmd = "P0;11z\\P0;21;255z\\P0;11z\\"; -- commence speech & report back when done EnterLarkState: PUBLIC ENTRY PROC[ info: LarkInfo, newState: LarkState, sInfo: SmartsInfo, data: REF_NIL ] = { ENABLE UNWIND=>NULL; EnterLarkSt[info, newState, sInfo, data]; }; EnterLarkSt: PUBLIC INTERNAL PROC[ info: LarkInfo, newState: LarkState, sInfo: SmartsInfo, data: REF ]={ ENABLE UNWIND=>NULL; newSpec: LIST OF ThSmartsPrivate.LarkStateSpec = LIST[[newState, sInfo]]; trans: LSTrans _ lsTrans[info.larkState][newState]; oldState: LarkState = info.larkState; cDesc: ConvDesc_NIL; keyTable: Lark.KeyTable; sw: BOOL_FALSE; otherAction: REF_NIL; toneSpec: LarkPlay.ToneSpec _ NIL; newProses: Thrush.ProseSpecs _ NIL; IF pd.tonesInvalid THEN SetTones[]; SELECT trans FROM nop => RETURN; -- Certifiably nothing at all to do, or inappropriate time to do it. set => { info.larkState_newState; RETURN; }; X => { LarkProblem["%g: Invalid LarkState Transition", sInfo]; RETURN; }; rec => { info.larkState_recovering; LarkFailed[sInfo]; --RETURN--}; fai => { info.larkState _ failed; LarkProblem["%g: Lark failure requested by server", sInfo]; info.larkProcess _ NIL; NOTIFY info.stateChange; -- Be sure process notices failure and disappears. RETURN; }; ENDCASE; IF sInfo#NIL THEN cDesc _ ThSmartsPrivate.GetConvDesc[sInfo]; IF cDesc#NIL THEN { IF cDesc.newKeys THEN keyTable _ cDesc.cState.keyTable; IF cDesc.newSpec THEN { spec: Lark.ConnectionSpec _ info.spec _ cDesc.cState.spec; cDesc.newSpec_FALSE; info.forwardedCall _ spec#NIL AND (spec.localSocket.net # spec.remoteSocket.net OR spec.localSocket.host # spec.remoteSocket.host); }; newProses _ cDesc.newProses; }; IF tSetFwd[trans] = setFwd THEN { newState _ IF info.forwardedCall THEN trunkForwarding ELSE trunkTalking; trans _ lsTrans[info.larkState][newState]; }; info.larkState_newState; SELECT tDisconn[trans] FROM disconnect => { IF ThNet.pd.debug THEN Deb[ info, 'd ]; QueueLarkAction[info, aDisconnect, sInfo]; }; ENDCASE; toneSpec _ SELECT trans FROM dia, diu => dialTone, -- to handset receiver rbk, rbu => IF info.ringTune#NIL THEN info.ringTune ELSE ringbackTone, bzy, bzu => busyTone, err, eru => errorTone, rng, rgu => info.ringTune, ENDCASE => NIL ; SELECT tDoTones[trans] FROM doTones => { IF ThNet.pd.debug THEN Deb[ info, 'T ]; IF toneSpec#NIL THEN QueueLarkAction[info, toneSpec, sInfo]; }; stopTones => { IF ThNet.pd.debug THEN Deb[ info, 't ]; QueueLarkAction[info, aNoTones, sInfo]; }; ENDCASE; IF newProses#NIL THEN SELECT trans FROM sup, spn, tlk => { reqProseSpecs, lastReqProseSpecs: Thrush.ProseSpecs _ NIL; FOR pL: Thrush.ProseSpecs _ newProses, pL.rest WHILE pL#NIL DO pS: Thrush.ProseSpec = pL.first; IF pS.type = request THEN { elt: Thrush.ProseSpecs _ LIST[pS]; IF reqProseSpecs=NIL THEN reqProseSpecs _ elt ELSE IF lastReqProseSpecs=NIL THEN Thrush.pERROR ELSE lastReqProseSpecs.rest _ elt; lastReqProseSpecs _ elt; }; ENDLOOP; IF reqProseSpecs#NIL THEN { IF ThNet.pd.debug THEN Deb[info, 'P, rope[newProses.first.prose], IF newProses.rest#NIL THEN rope[" ... MORE"] ELSE [null[]]]; QueueLarkAction[info, reqProseSpecs, sInfo]; }; }; ENDCASE; SELECT tHookState[trans] FROM reset => { info.spec _ NIL; SELECT info.hookState FROM spkr, monitor => { info.hookState_onhook; info.terminalType_std; }; -- going totally idle ENDCASE; }; spkrTrans => IF info.hookState=onhook THEN {-- dialtone, direct connect or ringback, Hafra info.hookState _ spkr; info.terminalType _ IF sInfo.larkInfo.radio THEN radio ELSE spkr; }; ENDCASE; -- no state change cases. sw_FALSE; IF info.terminalType#info.lastTerminalType THEN sw_TRUE; SELECT tSwitch[trans] FROM switch => sw_TRUE; switchIfDiff => IF oldState { IF ThNet.pd.debug THEN Deb[info, 'F]; QueueLarkAction[info, RopeToDTMF[NARROW[data]], sInfo]; }; ENDCASE; IF keyTable#NIL THEN SELECT tSetKey[trans] FROM setKey => { IF ThNet.pd.debug THEN Deb[info, 'K]; cDesc.newKeys_FALSE; QueueLarkAction[info, keyTable, sInfo]; }; ENDCASE; IF info.spec#NIL THEN SELECT trans FROM sup, spn, tlk, frd, frn => { spec: Lark.ConnectionSpec = info.spec; info.spec _ NIL; IF ThNet.pd.debug THEN Deb[info, 'C, int[LOOPHOLE[spec.localSocket.socket]], int[LOOPHOLE[spec.remoteSocket.socket]], card[spec.remoteSocket.net], card[spec.remoteSocket.host]]; QueueLarkAction[info, spec, sInfo]; }; ENDCASE; IF otherAction#NIL THEN { IF ThNet.pd.debug THEN Deb[info, 'O]; QueueLarkAction[info, otherAction, sInfo]; }; IF info.newActions=NIL THEN RETURN; }; LarkFailed: PUBLIC ERROR [sInfo: SmartsInfo] = CODE; TonesDone: PUBLIC ENTRY PROC[info: LarkInfo, commandEvent: Lark.StatusEvent, sInfo: SmartsInfo ] = { Deb[info, 'z]; SELECT commandEvent.event FROM 'F=> -- Feeping complete { IF info.larkState#trunkSignalling THEN RETURN; EnterLarkSt[info, trunkTalking, sInfo, NIL]; }; ENDCASE => -- other tones finished. QueueLarkAction[info, NEW[ATonesDoneType _ [commandEvent.event]], sInfo]; }; FlashWait: PUBLIC ENTRY PROC[info: LarkInfo, sInfo: SmartsInfo ] = TRUSTED { ENABLE UNWIND => NULL; flashWait: CONDITION; IF info=NIL THEN RETURN; Process.SetTimeout[@flashWait, Process.MsecToTicks[pd.flashWaitTime]]; -- 600 ms or so. Deb[info, 'w]; WAIT flashWait; Deb[info, 'W]; IF info.larkState=trunkTalking THEN -- nothing has gone wrong []_QueueCommandSequence[info, larkCommands[info.terminalType][info.larkState], @info.lState, info.scratchEv, sInfo]; }; QueueFeeps: PUBLIC PROC[sInfo: SmartsInfo, feeps: Thrush.ProseSpecs ] = { FOR pS: Thrush.ProseSpecs _ feeps, pS.rest WHILE pS#NIL DO EnterLarkState[sInfo.larkInfo, trunkSignalling, sInfo, pS.first.prose]; ENDLOOP }; ProseControlDone: PUBLIC INTERNAL PROC[info: LarkInfo, marker: INT, sInfo: SmartsInfo] = { IF marker=ThSmartsPrivate.proseFailure THEN { LarkProblem["Text-to-speech service failed", sInfo]; Fail[info]; } ELSE QueueLarkAction[info, NEW[ASpeechDoneType _ [marker]], sInfo]; }; FailE: ENTRY PROC[info: LarkInfo] = {Fail[info];}; Fail: INTERNAL PROC[info: LarkInfo] = { IF info.larkState#recovering THEN info.larkState_failed; }; LarkSupervisor: PROCEDURE[ info: LarkInfo, sInfo: SmartsInfo ] = { ENABLE UNWIND => NULL; req: REF; WaitForAction: ENTRY PROC[info: LarkInfo] RETURNS [ref: REF_NIL] = TRUSTED { ENABLE UNWIND=>NULL; DO elt: LIST OF REF _ info.newActions; IF info.larkState=failed OR info.larkState=recovering THEN RETURN[NIL]; IF elt # NIL THEN { ref_elt.first; info.newActions _ elt.rest; RETURN[ref]; }; Process.SetTimeout[@info.stateChange, Process.MsecToTicks[pd.idleWaitTime]]; WAIT info.stateChange; IF info.newActions = NIL THEN { IF info.nextToneList#NIL THEN Fail[info]; -- Notification is late. RETURN[NIL]; }; ENDLOOP; }; info.larkToneSpec _ NEW[Lark.ToneSpecRec _ [volume: 0, totalTime: 0, tones: NIL]]; TRUSTED { Process.EnableAborts[@info.stateChange]; }; WHILE (req_WaitForAction[info])#NIL DO -- Deal with communications failure. ENABLE { RPC.CallFailed => IF pd.callTimeoutOK THEN RESUME ELSE { LarkProblem["%g: Call Failed", sInfo]; GOTO Failed; }; ABORTED => { LarkProblem["%g: LarkSupervisor aborted", sInfo]; GOTO Failed; }; }; DoTones: PROC[newTones: BOOL] = { -- Does one tone from current list of tones IF info.nextToneList=NIL THEN RETURN; info.larkToneSpec.volume _ info.toneSpec.volume; info.expectedNotification _ IF info.expectedNotification='z THEN 'a ELSE info.expectedNotification+1; info.larkToneSpec.notification _ [tones, info.expectedNotification]; info.larkToneSpec.tones _ info.nextToneList.first; []_info.interface.SpecifyTones[shh: info.shh, queueIt: ~newTones, tones: info.larkToneSpec]; }; SpeakText: PROC = { textPkt: Rope.ROPE; IF ~info.textToSpeech OR info.flushInProgress THEN RETURN; WHILE info.pktsOutstanding < numPkts AND info.textToSpeak.Length[] > 0 DO proseText: Rope.ROPE _ info.textToSpeak; IF proseText.Length[] <= maxTextPktLen THEN { textPkt _ Rope.Concat[proseText, speechDone]; info.textToSpeak _ ""; info.ctrlMarkerQueue _ List.Nconc1[info.ctrlMarkerQueue, NEW[INT _ speechDoneMarker]]; } ELSE { index: INT _ maxTextPktLen; WHILE IO.TokenProc[Rope.Fetch[proseText, index-1]] = other DO index _ index-1; IF index=0 THEN {index _ maxTextPktLen; EXIT}; ENDLOOP; IF Rope.Fetch[proseText, index-1] = IO.ESC THEN index _ index-1 ELSE IF Rope.Fetch[proseText, index-2] = IO.ESC THEN index _ index-2; info.controlMarker _ IF info.controlMarker>=ThSmartsPrivate.maxControlMarker THEN minControlMarker ELSE info.controlMarker+1; textPkt _ Rope.Cat[cmdLeader, Convert.RopeFromInt[info.controlMarker], indexMarkerEnd, proseText.Substr[len: index]]; info.textToSpeak _ proseText.Substr[start: index]; info.ctrlMarkerQueue _ List.Nconc1[info.ctrlMarkerQueue, NEW[INT _ info.controlMarker]]; }; Deb[info, 'p, rope[textPkt]]; info.interface.CommandString[shh: info.shh, device: keyboard, commands: textPkt]; info.pktsOutstanding _ info.pktsOutstanding+1; ENDLOOP; }; WITH req SELECT FROM d: REF ADisconnectType => { info.interface.Disconnect[ shh: info.shh, buffer: out1]; info.interface.Disconnect[ shh: info.shh, buffer: in1]; }; ts: LarkPlay.ToneSpec => { info.toneSpec_ts; info.nextToneList _ info.toneSpec.tones; DoTones[TRUE]; }; ps: Thrush.ProseSpecs => { IF ~info.textToSpeech THEN LOOP; FOR proseS: Thrush.ProseSpecs _ ps, proseS.rest WHILE proseS#NIL DO pSpec: Thrush.ProseSpec = proseS.first; newText: Rope.ROPE; IF ~pSpec.queueIt THEN ProseFlush[info, stopAndFlush]; newText _ IF pSpec.direction=record -- really want BOOLEAN pSpec.filter THEN pSpec.prose -- allows client to send Prose reset ELSE Rope.Translate[base: pSpec.prose, translator: FilterText]; info.textToSpeak _ Rope.Concat[info.textToSpeak, newText]; info.clientMarker _ IF info.clientMarker = ThSmartsPrivate.maxClientMarker THEN minClientMarker ELSE info.clientMarker + 1; EnterProseQueue[info, pSpec, info.clientMarker]; info.textToSpeak _ Rope.Cat[info.textToSpeak, cmdLeader, Convert.RopeFromInt[info.clientMarker], indexMarkerEnd]; ENDLOOP; SpeakText[]; }; pd: REF ASpeechDoneType => { marker: REF INT _ NIL; IF pd.indexMarker = ThSmartsPrivate.flushMarker THEN { info.flushInProgress _ FALSE; info.ctrlMarkerQueue _ NIL; info.pktsOutstanding _ 0; SpeakText[]; } ELSE { IF info.ctrlMarkerQueue = NIL THEN { LarkProblem["Text-to-speech service: empty control marker list", sInfo]; GOTO Failed; }; marker _ NARROW[info.ctrlMarkerQueue.first]; IF pd.indexMarker = marker^ THEN { info.ctrlMarkerQueue _ info.ctrlMarkerQueue.rest; info.pktsOutstanding _ info.pktsOutstanding-1; SpeakText[]; } ELSE { LarkProblem["Text-to-speech service: wrong marker received", sInfo]; GOTO Failed; }; }; }; td: REF ATonesDoneType => IF info.toneSpec#NIL THEN { IF td.event#info.expectedNotification THEN GOTO Failed; IF info.nextToneList#NIL AND info.nextToneList.rest#NIL THEN info.nextToneList _ info.nextToneList.rest ELSE IF NOT info.toneSpec.repeatIndefinitely THEN { info.toneSpec_NIL; info.nextToneList_NIL } ELSE info.nextToneList _ info.toneSpec.tones; IF info.nextToneList#NIL THEN DoTones[FALSE]; }; a: REF ANoTonesType => { info.toneSpec_NIL; info.nextToneList_NIL; quenchSpec.tones.first.on _ 0; []_info.interface.SpecifyTones[shh: info.shh, tones: quenchSpec, queueIt: FALSE]; }; resetAction: REF ResetActionType => { []_info.interface.Reset[shh: info.shh, rName: "Don't revert"]; ProseFlush[info, pReset]; }; echoParameters: Lark.EchoParameters => []_info.interface.EchoSupression[shh: info.shh, echo: echoParameters]; commands: Lark.CommandEvents => IF commands#NIL THEN IF commands[0].device=touchPad THEN { quenchSpec.tones.first.on _ pd.waitForTelco; []_info.interface.SpecifyTones[shh: info.shh, tones: quenchSpec, queueIt: FALSE]; []_info.interface.Feep[shh: info.shh, on: pd.telcoMinOn, off: pd.telcoMinOff, notify: [tones, 'F], waveTable: ThNet.pd.feepVolume, queueIt: TRUE, events: commands]; } ELSE info.interface.Commands[ info.shh, commands ]; keyTable: Lark.KeyTable => info.interface.SetKeyTable[shh: info.shh, table: keyTable]; spec: Lark.ConnectionSpec => { spec.buffer _ out1; info.interface.Connect[shh: info.shh, specs: spec ]; spec.buffer _ in1; info.interface.Connect[shh: info.shh, specs: spec ]; }; ENDCASE; REPEAT Failed => { FailE[info]; }; ENDLOOP; info.larkProcess _ NIL; }; FilterText: Rope.TranslatorType = { -- PROC [old: CHAR] RETURNS [new: CHAR] SELECT old FROM IO.TAB, IO.LF, IO.CR, IO.ESC => new _ old; -- Don't allow user to send reset (ControlR) < IO.SP => new _ IO.SP; ENDCASE => new _ old; }; ProseFlush: PROC[info: LarkInfo, proseCmd: ProseCmd] = { info.textToSpeak _ ""; IF ~info.flushInProgress THEN { info.interface.CommandString[shh: info.shh, device: keyboard, commands: proseCmd]; info.flushInProgress _ TRUE; }; }; EnterProseQueue: ENTRY PROC[info: LarkInfo, pS: Thrush.ProseSpec, internalClientMarker: INT] = { elt: ThSmartsPrivate.LarkProseQueue _ LIST[[pS, internalClientMarker]]; IF info.proseQueue=NIL THEN info.proseQueue _ elt ELSE IF info.pTail=NIL THEN Thrush.pERROR ELSE info.pTail.rest _ elt; info.pTail _ elt; }; QueueLarkAction: INTERNAL PROC[info: LarkInfo, ref: REF, sInfo: SmartsInfo] = { elt: LIST OF REF = LIST[ref]; lst: LIST OF REF = info.lastAction; IF info.newActions=NIL THEN info.newActions _ elt ELSE IF lst=NIL THEN Thrush.pERROR ELSE lst.rest _ elt; info.lastAction _ elt; IF info.larkProcess=NIL THEN TRUSTED { Process.Detach[info.larkProcess _ FORK LarkSupervisor[ info, sInfo ]]; }; NOTIFY info.stateChange; }; LarkProblem: PROC[remark: ROPE, sInfo: SmartsInfo] = { Log.ProblemFR[remark, $Lark, sInfo.larkInfo, TU.RefAddr[sInfo]]; }; QueueCommandSequence: INTERNAL PROC[ info: LarkInfo, commands: ROPE, lState: LONG POINTER TO LState, scratchEv: Lark.CommandEvents, sInfo: SmartsInfo] RETURNS[otherAction: REF_NIL]= TRUSTED { eventIndex: INTEGER_-1; c: CHAR; i: NAT; index: INTEGER; event: Lark.Event; events: Lark.CommandEvents _ scratchEv; nextState: LState _ []; len: NAT; IF commands=NIL THEN RETURN; -- status quo len _ commands.Length[]; FOR i IN [0..len) DO SELECT (c_commands.Fetch[i]) FROM 'J, 'j => IF ~pd.backDoorOH THEN LOOP; ENDCASE; SELECT c FROM 'Z => { lState^_ []; otherAction _ resetAction; }; 'X, 'x => { row: NAT_ Digit[commands.Fetch[i+1]]; outputs: PACKED ARRAY [0..8) OF BOOLEAN _ LOOPHOLE[nextState.xbar[row]]; outputs[Digit[commands.Fetch[i+2]]] _ (c='X); nextState.xbar[row] _ LOOPHOLE[outputs]; i_i+2; LOOP; }; 'E, 'e => { nextState.echoStyle _ commands.Fetch[i_i+1]-'0; otherAction _ echosOn[nextState.echoStyle]; }; 'M, 'm => { nextState.voiceMode _ SELECT commands.Fetch[i_i+1] FROM '0 => Lark.o3i1, '1 => Lark.o2i2, '2 => Lark.o1i1, ENDCASE => ERROR; }; ENDCASE=> { IF c IN ['a..'z] THEN { event _ Lark.disabled; c_c-('a-'A); } ELSE event _ Lark.enabled; IF lStateForLetter[c]#none THEN nextState.lSw[lStateForLetter[c]] _ event; }; ENDLOOP; IF nextState=lState^ THEN RETURN; IF nextState.echoStyle#lState.echoStyle AND otherAction=NIL THEN otherAction _ echosOff[lState.echoStyle]; FOR iteration: NAT IN [0..1] DO -- 0: compute size; 1: fill in result sequence. index_-1; IF nextState.voiceMode#lState.voiceMode THEN events[index_index+1] _ [voiceMode, nextState.voiceMode]; FOR i: LSwitches DECREASING IN LSwitches DO IF nextState.lSw[i]#lState.lSw[i] THEN events[index_index+1] _ [lDevs[i], nextState.lSw[i]]; ENDLOOP; FOR i: NAT IN [0..8) DO IF nextState.xbar[i]#lState.xbar[i] THEN { outputs: PACKED ARRAY[0..8) OF BOOLEAN = LOOPHOLE[lState.xbar[i]]; nxtOutputs: PACKED ARRAY[0..8) OF BOOLEAN = LOOPHOLE[nextState.xbar[i]]; FOR j: NAT IN [0..8) DO IF outputs[j]#nxtOutputs[j] THEN events[index_index+1] _ [ Lark.Device[LOOPHOLE[IF nxtOutputs[j] THEN 23 ELSE 22]], LOOPHOLE[i*16+j] ]; ENDLOOP; }; ENDLOOP; IF index=-1 THEN { events_NIL; EXIT; }; IF iteration=0 THEN events _ NEW[Lark.CommandEventSequence[index+1]]; ENDLOOP; QueueLarkAction[info, events, sInfo]; lState^ _ nextState; lState.lSw[xBarAll] _ Lark.disabled; }; Digit: PROC[c: CHAR] RETURNS [digit: NAT] = INLINE { RETURN[c-'0]; }; RopeToDTMF: PROC [r: Thrush.ROPE] RETURNS [ce: Lark.CommandEvents] = { len: INT _ MIN[Lark.Passel.LAST, r.Length[]]; ce _ NEW[Lark.CommandEventSequence[len]]; FOR j: INT IN [0..ce.length) DO c: CHAR = r.Fetch[j]; ce.e[j] _ [touchPad, SELECT c FROM IN ['0..'9] => LOOPHOLE[128 + c - '0], IN ['a..'d] => LOOPHOLE[138 + c - 'a], IN ['\001..'\037] => LOOPHOLE[LOOPHOLE[c,INTEGER]*10], -- 100 ms. pauses, 12-14 illegal! '* => Lark.bStar, '# => Lark.bThorp, ENDCASE => Lark.bStar]; ENDLOOP; }; SetTones: INTERNAL PROC[] = { IF ~pd.tonesInvalid THEN RETURN; pd.tonesInvalid _ FALSE; dialTone _ NEW[LarkPlay.ToneSpecRec _ [repeatIndefinitely: TRUE, volume: ThNet.pd.tonesVolume, tones: LIST[LIST[ [f1: 350, f2: 440, on: 5000, off: 0], [f1: 350, f2: 440, on: 5000, off: 0]]]]]; busyTone _ NEW[LarkPlay.ToneSpecRec _ [repeatIndefinitely: TRUE, volume: ThNet.pd.tonesVolume, tones: LIST[LIST[ [f1: 480, f2: 620, on: 500, off: 500, repetitions: 5], [f1: 480, f2: 620, on: 500, off: 500, repetitions: 5]]]]]; errorTone _ NEW[LarkPlay.ToneSpecRec _ [repeatIndefinitely: TRUE, volume: ThNet.pd.tonesVolume, tones: LIST[LIST[ [f1: 480, f2: 620, on: 250, off: 250, repetitions: 10], [f1: 480, f2: 620, on: 250, off: 250, repetitions: 10]]]]]; ringbackTone _ NEW[LarkPlay.ToneSpecRec _ [repeatIndefinitely: TRUE, volume: ThNet.pd.tonesVolume, tones: LIST[LIST[ [f1: 440, f2: 480, on: 2000, off: 4000], [f1: 440, f2: 480, on: 2000, off: 4000]]]]]; }; Deb: PROC[info: LarkInfo, c: CHAR, p1, p2, p3, p4: IO.Value_[null[]]] = { s: IO.STREAM; IF ~ThNet.pd.debug THEN RETURN; s_IO.ROS[]; s.PutF["<%g", char[c]]; SELECT c FROM 'M, 'P, 'p => s.PutF["-- %g", p1]; 'C => { s.PutF[" -- [%b, %b]", p3, p4]; s.PutF[" %b(%d), %b(%d)", p1, p1, p2, p2]; }; ENDCASE; s.PutRope[">\r"]; Log.Report[s.RopeFromROS[], $LarkDetailed, info]; }; QuickState: ARRAY LarkState OF IO.Value = [ rope["none"], rope["idle"], rope["talking"], rope["trunkSignalling"], rope["trunkTalking"], rope["trunkForwarding"], rope["trunkFlashing"], rope["failed"], rope["recovering"], rope["ringing"], rope["silence"], rope["dialTone"], rope["ringBack"], rope["busyTone"], rope["errorTone"]]; toneStdCommand: ROPE = "SX01X14X06"; toneSpkrCommand: ROPE = "LSX03X14X06"; toneMonitorCommand: ROPE = "SX01X03X14X06"; silentSignalling: ROPE _ "HIX02X14"; noisySignalling: ROPE _ "HISTX02X10X21X26X14"; -- same as trunk talking (feedback problems?) noisierSignalling: ROPE _ "HITLX02X30X23X26X24"; -- same as spkr trunk talking (feedback problems?) trunkSignalling: ROPE _ silentSignalling; larkCommands: ARRAY TerminalType OF ARRAY LarkState OF ROPE _ [ [ NIL, -- none "Z", -- idle "SX01X06X10X14", -- talking trunkSignalling, -- trunkSignalling "HISTX02X10X21X26X14", -- trunkTalking, codec-assisted electronic mode "E3HIX02X20X24", -- trunkForwarding, trunk to remote Lark connection. (need gain setting for echo?) "Z", -- trunkFlashing, on-hook for a second. "Z", -- failed "Z", -- recovering "RX03X06", -- ringing "SX14", -- silence toneStdCommand, toneStdCommand, toneStdCommand, toneStdCommand -- tones ], [ NIL, -- none "Z", -- idle "E1LX03X06X30X14", -- talking "HIX02X14X06", -- trunkSignalling "E2M1THILX30X02X25X26X24X53", -- trunkTalking, gain-controlled digital mode "E3HIX02X20X24", -- trunkForwarding; device stuff for this mode doesn't have much meaning. "Z", -- trunkFlashing, on-hook for a second. "Z", -- failed "Z", -- recovering "RX03X06", -- ringing "LX14", -- silence toneSpkrCommand, toneSpkrCommand, toneSpkrCommand, toneSpkrCommand -- tones ], [ NIL, -- none "Z", -- idle "SX01X03X06X10X14", -- talking "HIX02X14X06", -- trunkSignalling "HISTLX02X10X21X23X14X26", -- trunkTalking, codec-assisted electronic mode "E3HIX02X20X24", -- trunkForwarding, trunk to remote Lark connection. (meaning?) "Z", -- trunkFlashing, on-hook for a second. "Z", -- failed "Z", -- recovering "RX03X06", -- ringing "SX14", -- silence toneMonitorCommand, toneMonitorCommand, toneMonitorCommand, toneMonitorCommand -- tones ], [ NIL, -- none "Z", -- idle "SX01X06X60X14", -- talking "HIX02X14X06", -- trunkSignalling "HITX02X60X21X26X64", -- trunkTalking "E3HIX02X20X24", -- trunkForwarding, trunk to remote Lark connection. (meaning?) "Z", -- trunkFlashing "Z", -- failed "Z", -- recovering "RX03X06", -- ringing "SX14", -- silence toneStdCommand, toneStdCommand, toneStdCommand, toneStdCommand -- tones ] ]; echoStyleFD: REF _ NEW[Lark.EchoParameterRecord _[ buffer: out1, buffer2Controlled: FALSE, buffer1Controlled: TRUE, decayTime: 5, gain: [ 1024, 2048, 2048, 2048, 32767 ] ]]; echoStyleFwd: REF _ echoStyleFD; echoStyleBD: REF _ NEW[Lark.EchoParameterRecord _[ buffer: in2, buffer2Controlled: FALSE, buffer1Controlled: TRUE, decayTime: 10, gain: [ 2048, 4096, 8192, 16384, 32767 ] ]]; echoStyleNoFD: REF _ NEW[Lark.EchoParameterRecord _[ buffer: out1, -- not interesting buffer2Controlled: FALSE, buffer1Controlled: FALSE, decayTime: 5, gain: [ 32767, 32767, 32767, 32767, 32767 ] ]]; echoStyleNoFwd: REF _ echoStyleNoFD; echoStyleNoBD: REF _ NEW[Lark.EchoParameterRecord _[ buffer: in2, -- not interesting buffer2Controlled: FALSE, buffer1Controlled: FALSE, decayTime: 5, gain: [ 32767, 32767, 32767, 32767, 32767 ] ]]; echosOn: ARRAY [0..3] OF REF_[ NIL, echoStyleFD, echoStyleBD, echoStyleFwd ]; echosOff: ARRAY [0..3] OF REF_[ NIL, echoStyleNoFD, echoStyleNoBD, echoStyleNoFwd ]; LSwitches: TYPE = ThSmartsPrivate.LSwitches; LState: TYPE = ThSmartsPrivate.LState; lDevs: ARRAY LSwitches OF Lark.Device = [ crossBar, offHookRelay, aRelay, sideTone, ringEnable, revertRelay, revertHookswitch, led, spMode, crossBar--random...not used-- ]; lStateForLetter: ARRAY CHAR['A..'Z] OF LSwitches = [ none, none, none, none, none, -- A to E revert, revertHook, hook, aSwitch, hook, none, led, -- F to L none, none, none, none, none, -- M to Q ringO, sideTone, spMode, none, none, none, none, none, -- R to Y none -- Z -- ]; LSTrans: TYPE = { nop, -- nothing to do set, -- enter specified state (usu. step to recovery) without taking any other actions. zap, zpu, zpn, -- reset Lark hardware (u means unconnect first, n means silence tones first) trk, tkn, -- Set for electronic phone connection (n means silence tones first) frd, frn, -- Trunk-to-network forwarding versions of trk, tkn (frn probably doesn't exist; wrong end <>) tlk, -- like supervision, but must also adjust switching. sup, spn, -- supervision, OK to change connection, key table. (n means silence tones first) ksp, -- key supervision, OK to change key table. sgl, sgn, -- Do trunk signalling (n means silence tones first) fls, -- Flash the phone line rng, rgu, -- Set for ringing (u means unconnect first, r means repeating tone) dia, diu, -- Set for dial tone (tones should be more generic and user-programmable than this!) rbk, rbu, -- Set for ring back bzy, bzu, -- Set for busy tone err, eru, -- Set for error tone sil, -- silence tones, ksp obtains fai, -- enter failed state, by Smarts-level request. Don't complain, just do it. Make sure process goes away. rec, -- move from failed state to recovering state, but complain to caller that Lark has failed, via signal. X -- invalid transition; complain, then remain in present state (go idle?) }; lsTrans: ARRAY LarkState OF ARRAY LarkState OF LSTrans = [[ nop, zap, X, X, X, X, X, X, X, X, X, X, X, X, err ],[-- non (none) X, nop, spn, sgl, trk, frd, X, fai, X, rng, nop, dia, rbk, bzy, err ],[-- idl (idle) X, zpu, sup, X, X, X, X, fai, X, rgu, nop, diu, rbu, bzu, eru ],[-- tlk (talking) X, zpn, X, ksp, trk, frd, X, fai, X, X, nop, X, X, X, X ],[-- sig (trkSignalling) X, zap, X, sgl, ksp, X, fls, fai, X, X, nop, X, X, X, X ],[-- trk (trkTalking) X, zpu, X, sgl, X, sup, X, fai, X, X, nop, diu, rbu, bzu, eru ],[-- fwd (trkForwarding) X, zap, X, X, trk, X, sup, fai, X, X, nop, X, X, X, X ],[-- fls (trkFlash) set, rec, rec, rec, rec, rec, rec, set, set, rec, rec, rec, rec, rec, rec ],[-- fai (failed) set, nop, nop, nop, nop, nop, nop, nop, nop, nop, nop, nop, nop, nop, nop ],[-- rec (recovering) X, zpn, spn, sgn, tkn, frn, X, fai, X, ksp, sil, dia, rbk, bzy, err ],[-- rng (ringing) X, zap, tlk, sgl, trk, frd, X, fai, X, rng, ksp, dia, rbk, bzy, err ],[-- shh (silence) X, zpn, spn, sgn, tkn, frn, X, fai, X, rng, sil, ksp, rbk, bzy, err ],[-- dia (dialTone) X, zpn, spn, sgn, tkn, frn, X, fai, X, rng, sil, dia, ksp, bzy, err ],[-- rbk (ringBack) X, zpn, spn, sgn, tkn, frn, X, fai, X, rng, sil, dia, rbk, ksp, err ],[-- bzy (busyTone) X, zpn, spn, sgn, tkn, frn, X, fai, X, rng, sil, dia, rbk, bzy, ksp ] -- err (errorTone) ]; TDisconn: TYPE = { X, disconnect }; tDisconn: ARRAY LSTrans OF TDisconn = [ -- zpu, rgu, diu, rbu, bzu, eru X, X, X, disconnect, X, X, X, X, X, X, X, X, X, X, X, X, X, disconnect, X, disconnect, X, disconnect, X, disconnect, X, disconnect, X, X, X, X ]; TDoTones: TYPE = { X, doTones, stopTones }; tDoTones: ARRAY LSTrans OF TDoTones = [ -- rng, rgu, dia, diu, rbk, rbu, bzy, bzu, err, eru; zpn, tkn, spn, sgn, sil X, X, X, X, stopTones, X, stopTones, X, X, X, X, stopTones, X, X, stopTones, X, doTones, doTones, doTones, doTones, doTones, doTones, doTones, doTones, doTones, doTones, stopTones, X, X, X ]; THookState: TYPE = { X, reset, spkrTrans }; tHookState: ARRAY LSTrans OF THookState = [ -- zap, zpu, zpn; trk, tkn, tlk, spn, fls, dia, diu, rbk, rbu, bzy, bzu, err, eru, sil X, X, reset, reset, reset, spkrTrans, spkrTrans, X, X, spkrTrans, X, spkrTrans, X, X, X, spkrTrans, X, X, spkrTrans, spkrTrans, spkrTrans, spkrTrans, spkrTrans, spkrTrans, spkrTrans, spkrTrans, spkrTrans, X, X, X ]; TSwitch: TYPE = { X, switch, switchIfDiff }; tSwitch: ARRAY LSTrans OF TSwitch = [ -- zap, zpu, zpn, trk, tkn, frd, frn, tlk, spn, sgl, sgn, fls; rng, rgu, dia, diu, rbk, rbu, bzy, bzu, err, eru X, X, switch, switch, switch, switch, switch, switch, switch, switch, X, switch, X, switch, switch, switch, switchIfDiff, switchIfDiff, switchIfDiff, switchIfDiff, switchIfDiff, switchIfDiff, switchIfDiff, switchIfDiff, switchIfDiff, switchIfDiff, switch, X, X, X ]; TSetKey: TYPE = { X, setKey }; tSetKey: ARRAY LSTrans OF TSetKey = [ -- trk, tkn, frd, frn, tlk, sup, spn, ksp, sgl, sgn, fls, rng, rgu, dia, diu, rbk, rbu, bzy, bzu, err, eru, sil X, X, X, X, X, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, X, X, X ]; TSetFwd: TYPE = { X, setFwd }; tSetFwd: ARRAY LSTrans OF TSetFwd = [ -- trk, tkn X, X, X, X, X, setFwd, setFwd, X, X, X, X, X, X, X, X, X, X, X, X, X, X, X, X, X, X, X, X, X, X, X ]; ADisconnectType: TYPE = { aDisconnect }; aDisconnect: REF ADisconnectType _ NEW[ADisconnectType_aDisconnect]; ResetActionType: TYPE = { resetAction }; resetAction: REF ResetActionType _ NEW[ResetActionType_resetAction]; ANoTonesType: TYPE = { aNoTones }; aNoTones: REF ANoTonesType _ NEW[ANoTonesType_aNoTones]; ATonesDoneType: TYPE = RECORD [ event: Lark.Event ]; ASpeechDoneType: TYPE = RECORD [ indexMarker: INT ]; ViewCmd: Commander.CommandProc = TRUSTED { Nice.View[pd, "Lark Out PD"]; }; Commander.Register["VuLarkOut", ViewCmd, "Program Management variables for Lark Output"]; }. όLarkOutImpl.mesa Copyright c 1985 by Xerox Corporation. All rights reserved. Polle Zellweger (PTZ) December 12, 1985 0:59:56 am PST Last modified by D. Swinehart, December 12, 1985 0:49:05 am PST Declarations <> definitions to interface to DECTalk text-to-speech synthesizer; more in ThSmartsPrivate DSR brief () not strictly needed for reset or flush, but makes the DECTalk (which is normally quiet in this case) respond more like the Prose. Byte (char) count; RPCLupine.maxDataLength is word count No bigger than RPCLupine.maxDataLength - 2*indexMarkerLen maxClientMarker: INT = 199; -- in ThSmartsPrivate maxControlMarker: INT = 250; -- in ThSmartsPrivate External Procedures Each select statement combines cases to execute a subset of the required actions efficiently. If trunkTalking was requested, we must enter either trunkTalking or trunkForwarding, depending on whether the other end of the connection is on the same machine. When leaving talking state but not going idle, must explicitly take down Ethernet connection. Does this ever happen? Queue up request to eliminate connections. Select tone/tune specifications. Go offhook and enter speakerphone mode if noises need to be heard and phone isn't offhook Go back onhook when idling from spkr (not sPkr) or monitor mode. <> Internal Procedures In a loop, keep the state of the Lark up to date. Awakens itself whenever any pending tone is otherwise likely to time out. Awakened by EnterLarkState whenever the state of tones, switches, and the like might have to change. sInfo is the SmartsInfo in use when the process was initiated. It's used to report errors, but bear in mind that it may or may not be the one in effect when a particular complaint occurs. speechDone (or some control marker) is needed to keep the Prose going if new text comes in after the last bit of the previous request was sent, but before the Prose finishes speaking it. Triggers a call from LarkInImpl.HandleProseOutput. Scan backward from the end of the packet for a place to break between words. The Prose treats an index marker as a word terminator. Keep punctuation with its preceding word for correct prosodics. Too long between break chars; just make progress somehow. Make sure not to break in the middle of a client marker!! Maybe just as satisfactory to treat each elt of list as separate request & terminate with CommenceSpeech to keep Prose going. < revert. Remember to change 2d parameter next time Lark.mesa changes.>> Connect output buffer Remove chars that the Prose considers illegal. Called only from LarkSupervisor, whose sequentiality implies that no locks are needed. This list is a queue - you expect the notifications to return in the order you sent them. LarkSupervisor "fails" if you don't get back the first thing in the queue. Queue is a FIFO list of REFs, with a lastAction pointer to aid in rapid enqueuing. Hardware Switching Tables Interpretation of the command string characters: En-- echo mode; n IN [0..3); selects echoStyleStd (default), ...FD, ...BD, or ...Fwd F -- T/R lead reversion G -- A/A1 hookswitch control reversion H -- Assert Telewall hookswitch I -- Assert A/A1 to Telewall J -- Assert Telewall hookswitch, maybe (depends on boolean variable) L -- Lights led R -- overrides volume control for ringing through speaker S -- enables telset sidetone T -- spMode; configures codecs for electronic trunk action Xij -- connects crossbar input i to output j Mn -- voiceMode; n IN [0..2); selects program O3I1 (default), O2I2, or O1I1 Z -- Resets hardware and crossbar Crossbar Connections: Port Input Output 0 dec1 co1 1 Xmtr Rcvr 2 from Telewall to Telewall 3 mike speaker 4 silence DTMF receiver 5 dec2 co2 6 line 1 out line 1 in 7 line 2 out line 2 in Telset "STX02X10X21X26X14", -- trunkFlashing, on-hook but otherwise unchanged. Speakerphone "TLX02X30X23X26X24", -- trunkFlashing Monitoring Telset "STLX10X21X23X14X26", -- trunkFlashing Radio Input, Telset/radio monitoring "STLX10X21X23X14X26", -- trunkFlashing Front Door call using Speakerphone Back Door call using Speakerphone Standard FD or BD handset mode, no forwarding Standard FD or BD handset mode, no forwarding State tables non idl tlk sig trk fwd fls fai rec rng shh dia rbk bzy err _new old \/ Subtransition codes and tables Queued specifications for Supervisor Swinehart, June 14, 1985 5:22:47 pm PDT Repair Echo stuff changes to: resetAction (local of LarkSupervisor) explicitly request resets on Z, LarkSupervisor ditto, QueueCommandSequence larkCommands, echosOn, echosOff, ZapEchosType, zapEchos, ANoTonesType, echoStyleNoFD, echoStyleNoBD Swinehart, July 16, 1985 2:15:11 pm PDT Fixes to trunkSignalling, trunkForwarding changes to: EnterLarkSt Swinehart, August 6, 1985 2:12:11 pm PDT Merge with PTZ Prose additions changes to: EnterProseQueue, ASpeechDoneType, ViewCmd Polle Zellweger (PTZ) July 3, 1985 7:11:31 pm PDT changes to: DIRECTORY, EnterLarkSt, IntIDQueue, IntIDTranslate, IntIDTranslateBody, EnterIntIDQueue (local of LarkSupervisor), RemoveIntIDQueue (local of LarkSupervisor), LarkSupervisor, HandleProseOutput Polle Zellweger (PTZ) July 11, 1985 6:20:12 pm PDT changes to: indexMarkerEnd(public), maxClientMarker(public), LarkSupervisor, ps (local of LarkSupervisor), pd (local of LarkSupervisor), ProseControlDone, EnterProseQueue(replaced EnterIntIDQueue) removed: RemoveIntIDQueue (function now in LarkInImpl), minClientMarker, minControlMarker, maxControlMarker, speechDoneMarker, DIRECTORY, pResetConfirmOK, cmdLeader, indexMarkerLen, SpeakText (local of LarkSupervisor) Polle Zellweger (PTZ) July 16, 1985 6:40:42 pm PDT Fix multiple packets bug. changes to: LarkSupervisor -- add proseActive & handle incoming speechDoneMarkers correctly=> SpeakText (local of LarkSupervisor), ps (local of LarkSupervisor), pd (local of LarkSupervisor) Polle Zellweger (PTZ) July 18, 1985 5:18:49 pm PDT new version of SpeakText preloads Prose and then sends only 1 packet at a time. changes to: DIRECTORY, LarkOutImpl, LarkSupervisor, SpeakText (local of LarkSupervisor), pd (local of LarkSupervisor), SpeakText, ps (local of LarkSupervisor) Polle Zellweger (PTZ) July 19, 1985 6:34:34 pm PDT Make sure not to break in the middle of a client marker!! changes to: SpeakText (local of LarkSupervisor) Polle Zellweger (PTZ) July 30, 1985 4:41:39 pm PDT Lark now has its own copy of newProses; must prune out started and finished reports. changes to: EnterLarkSt Polle Zellweger (PTZ) August 19, 1985 5:03:15 pm PDT Handle Prose flushing. changes to: maxTextPktLen, maxPkts, numPkts, LarkSupervisor, SpeakText (local of LarkSupervisor), ps (local of LarkSupervisor), pd (local of LarkSupervisor), FilterText, ProseControlDone Polle Zellweger (PTZ) August 27, 1985 8:58:36 pm PDT Move local variables from LarkOutImpl.LarkSupervisor into LarkInfo record. These variables are locked by the serial nature of the Lark Supervisor rather than by explicit ENTRY procedures. Reset Prose at Lark startup & idle. changes to: DIRECTORY, ProseCmd, ProseControlDone, minControlMarker, LarkSupervisor, SpeakText (local of LarkSupervisor), ps (local of LarkSupervisor), pd (local of LarkSupervisor), resetAction (local of LarkSupervisor), FilterText, ProseFlush Polle Zellweger (PTZ) November 4, 1985 8:30:57 pm PST Eliminate failure on timeout when speaking text Κ!ρ˜šœ™Icodešœ Οmœ1™Ÿ*˜hJšœ˜—šœ™J˜š Οnœžœžœžœ@žœžœ˜nJšžœžœžœ˜J˜)J˜J˜—š   œžœžœžœ@žœ˜hJšžœžœžœ˜Jšœ žœžœ!žœ˜IJ˜3J˜%Jšœžœ˜J˜Jšœžœžœ˜Jšœ žœžœ˜Jšœžœ˜"Jšœžœ˜#Jšžœžœ ˜#J™]šžœž˜JšœžœŸD˜SJšœ"žœ˜,Jšžœ>žœ˜IJšœ7Ÿ œ˜Cšœ˜JšœV˜VJšœžœ˜JšžœŸ2˜KJšžœ˜Jšœ˜—Jšžœ˜—Jšžœžœžœ,˜=šžœžœžœ˜Jšžœžœ"˜7šžœžœ˜Jšœ:˜:Jšœžœ˜Jšœžœžœ/žœ1˜ƒJ˜—Jšœ˜J˜—šžœž˜!J™‘Jšœ žœžœžœ˜HJ˜*J˜—J˜J™]J™šžœž˜šœ˜J™*Jšžœžœ˜'Jšœ*˜*J˜—Jšžœ˜—J™ šœ žœž˜JšœŸ˜,Jš œ žœžœžœžœ˜FJ˜J˜J˜Jšžœž˜Jšœ˜—šžœž˜˜ Jšžœžœ˜'Jšžœ žœžœ(˜J˜ šžœžœ˜Jšœžœ˜"Jšžœžœžœžœžœžœžœžœ˜Jšœ˜J˜—Jšžœ˜—šžœžœžœ˜Jš žœžœ,žœžœžœžœ ˜~Jšœ,˜,J˜—Jšœ˜—Jšž˜—JšœY™YJ™@šžœž˜šœ ˜ Jšœ žœ˜šžœž˜JšœDŸ˜YJšžœ˜—J˜—šœ žœžœŸ.˜ZJšœ+žœžœžœ ˜[—JšžœŸ˜"—Jšœžœ˜ Jšžœ)žœžœ˜8šžœž˜Jšœ žœ˜Jš œ Οfœžœžœžœžœ˜IJšžœ˜—šžœžœžœ˜Jšžœžœ@˜Všœ(˜(JšœP˜P—šžœ žœ˜Jšœžœ˜,JšœŸD˜_J˜—Jšœ*˜*J˜—šžœž˜˜Jšžœžœ˜%Jšœ!žœ˜7Jšœ˜—Jšžœ˜—š žœ žœžœžœž˜/˜ Jšžœžœ˜%Jšœžœ˜J˜'J˜—Jšžœ˜—š žœ žœžœžœž˜'˜J˜&Jšœ žœ˜šžœžœ˜$Jšœžœ˜'Jšœžœ˜(Jšœ;˜;—J˜#J˜—Jšžœ˜—šžœ žœžœ˜Jšžœžœ˜%Jšœ*˜*J˜—Jšžœžœžœžœ˜#Jšœ˜—J˜Jš  œž œžœ˜4J˜š  œžœžœžœH˜dJ˜šžœž˜šœŸ˜Jšœ˜Jšžœ žœžœ˜.Jšœ'žœ˜,J˜—šžœŸ˜#Jšœžœ0˜I——J˜J˜—š   œžœžœžœ'žœ˜LJšžœžœžœ˜Jšœ ž œ˜Jšžœžœžœžœ˜JšœGŸ˜WJ˜Jšžœ ˜J˜šžœžŸ˜=J™1šœ˜JšœV˜V——J˜—J˜š  œžœžœ2˜Išžœ(žœžœž˜:JšœG˜GJšž˜—J˜—J˜š  œžœžœžœžœ˜Zšžœ$žœ˜-Kšœ4˜4Kšœ ˜ K˜—šž˜Jšœžœ%˜>—J˜——J™šœ™J˜Jš œžœžœ!˜2š œžœžœ˜'Jšžœžœ˜;J˜—š œž œ)˜BJšœV™VJšœT™TJšœ6™6J™ΌJšžœžœžœ˜Jšœžœ˜ J˜š  œžœžœžœžœžœžœ˜LJšžœžœžœ˜šž˜Jšœžœžœžœ˜#Jš žœžœžœžœžœ˜Gšžœžœžœ˜Jšœ˜J˜Jšžœ˜ J˜—JšœL˜LJšžœ˜šžœžœžœ˜Jšžœžœžœ Ÿ˜BJšžœžœ˜ J˜—Jšžœ˜—J˜—J˜Jšœžœ5žœ˜RJšžœ.˜5šžœžœž˜'JšŸ$˜$šžœ˜š žœžœžœžœžœ˜8Jšœ'žœ ˜6—šžœ˜ Jšœ2žœ ˜A—Jšœ˜—J˜š œžœ žœŸ+˜MJšžœžœžœžœ˜%Jšœ0˜0šœ˜Jšžœžœžœ˜I—JšœD˜DJšœ2˜2Jšœ\˜\J˜J˜—š  œžœ˜Jšœžœ˜Jšžœžœžœžœ˜:šžœžœž˜JJšœžœ˜(šžœ%žœ˜-šœ-˜-J™ξ—Jšœ˜Jšœ9žœžœ˜VJ˜—šžœ˜J™ΕJšœžœ˜šžœ6ž˜=Jšœ˜šžœ žœžœ˜/J™9—Jšž˜—Kšžœ"žœžœžœ˜?š žœžœ"žœžœžœ˜EK™9—Jšœžœ5žœžœ˜}Jšœu˜uJšœ2˜2Jšœ9žœžœ˜XJ˜—Jšœ˜JšœQ˜QJšœ.˜.Jšž˜—J˜—J˜šžœžœž˜šœžœ˜J˜8J˜7J˜—šœ˜Jšœ˜Jšœ(˜(Jšœžœ˜Jšœ˜—šœ˜Jšžœžœžœ˜ šžœ-žœžœž˜CJšœ'˜'Jšœžœ˜Jšžœžœ ˜6šœ žœŸ$˜IKšžœŸ$˜6Kšžœ;˜?—Jšœ:˜:šœžœ4˜JKšžœ˜Kšžœ˜—Jšœ0˜0defaultšœ8˜8Lšœ'˜'Lšœ˜—Jšžœ˜J™}—Kšœ ˜ Jšœ˜—šœžœ˜Jšœžœžœžœ˜šžœ-žœ˜6Kšœžœ˜Kšœžœ˜Kšœ˜Kšœ ž˜ Kšœ˜—šžœ˜šžœžœžœ˜$JšœH˜HJšžœ˜ J˜—Jšœž œ˜,šžœžœ˜"Jšœ1˜1Jšœ.˜.Jšœ ˜ J˜—šžœ˜JšœD˜DJšžœ˜ Jšœ˜—J˜—Jšœ˜—š œžœžœžœžœ˜5Jšžœ$žœžœ˜7š žœžœžœžœž˜˜>J™P—Jšœ˜J˜—šœ&˜&JšœF˜F—˜šžœ žœž˜šžœžœ˜&J˜,JšœJžœ˜Qšœb˜bJšœ*žœ˜B—J˜—Jšžœ/˜3——JšœV˜V˜J˜J˜5Jšœ™J˜J˜4J˜—Jšžœ˜—Jšžœ˜"Jšžœ˜—Jšœžœ˜J˜J˜—š  œŸ'˜KK™.šžœž˜KšžœžœžœžœžœžœžœžœŸ,˜WKš œžœžœ žœžœ˜Kšžœ˜—J˜—š  œžœ(˜8J™VKšœ˜šžœžœžœ˜KšœR˜RJšœžœ˜J˜—J˜—J™š œž œ>žœ˜aJšœ₯™₯Kšœ&žœ˜GKšžœžœžœžœžœ žœžœžœ˜wJšœ˜Jšœ˜J˜—Jšœ žœD™Sš œžœžœžœ˜OJš œžœžœžœžœ˜Jšœžœžœžœ˜#Jšžœžœžœžœžœžœžœžœ˜iJ˜šžœžœžœžœ˜&Jšœ"žœ#˜I—Jšžœ˜J˜—J˜š  œžœ žœ˜6Jšœ-žœ˜@J˜J˜—š œžœžœ˜$Jšœžœ˜Jšœžœžœžœ:˜QJšžœžœžœžœ˜(Jšœ žœ˜Jšœžœ˜Jšœžœ˜Jšœžœ˜J˜J˜'J˜Jšœžœ˜ Jš žœ žœžœžœŸ ˜*J˜šžœžœ ž˜Jš žœžœ žœžœžœžœ˜Qšžœž˜ Jšœ3˜3˜ Jšœžœ˜%Jš œ žœžœžœžœžœ˜HJ˜-Jšœžœ ˜(J˜Jšžœ˜Jšœ˜—˜ Jšœ/˜/J˜+Jšœ˜—˜ šœžœž˜7J˜J˜J˜Jšžœžœ˜—Jšœ˜—šžœ˜ šžœžœ žœ(˜=Jšžœ˜—Jšžœžœ+˜JJ˜——Jšžœ˜—Jšžœžœžœ˜!šžœ&žœ žœž˜@Jšœ)˜)—š žœ žœžœžœŸ/˜OJ˜ šžœ&ž˜,Jšœ9˜9—š žœž œ žœžœ ž˜RJšœ6žœ˜>—š žœžœžœžœžœ"žœ˜BJš œ žœžœžœžœžœ˜BJš œ žœžœžœžœžœ˜Hš žœžœžœžœžœž˜8˜Jš œ žœžœžœžœ˜8Jšžœ ˜—Jšžœ˜—Jšœžœ˜ —Jšžœ žœ žœžœ˜'Jšžœ žœ žœ&žœ˜N—J˜%J˜J˜$J˜J˜—Jš œžœžœžœ žœžœžœ ˜EJ˜š  œžœ žœžœ˜FJšœžœžœ žœ˜-Jšœžœ!˜)šžœžœžœž˜Jšœžœ˜šœžœž˜"Jšžœ žœ˜&Jšžœ žœ˜&Jš žœžœžœžœŸ!˜XJ˜J˜Jšžœ˜—Jšžœ˜—J˜J˜—š œž œ˜Jšžœžœžœ˜ Jšœžœ˜šœ žœ-žœ˜@šœ%ž œ˜/Jšœ%˜%Jšœ*˜*——šœ žœ-žœ˜@šœ%ž œ˜/Jšœ6˜6Jšœ;˜;——šœ žœ-žœ˜Ašœ%ž œ˜/Jšœ7˜7Jšœ<˜<——šœžœ-žœ˜Dšœžœž œ˜/Jšœ(˜(Jšœ-˜-——J˜J˜—š œžœžœžœ˜IJšœžœžœ˜ Jšžœžœžœ˜Jšœžœžœ˜ J˜šžœž˜ Jšœ"˜"˜J˜Jšœ*˜*Jšœ˜—Jšžœ˜—J˜J˜1J˜—šœ žœ žœžœ ˜+J˜EJ˜‹J˜IJ˜——™J˜Jšœžœ˜$Jšœžœ˜&Jšœžœ˜+Jšœ$˜$Jšœ\˜\Jšœc˜cJ˜)J˜™0JšžœŸR™TJ™J™&J™J™J™DJ™J™9J™J™:J™,J™KJ™!—™Itable2šΟi™Mš’ ™ Mš’ ™ Mš’™Mš’™Mš’™Mš’ ™ Mš’™Mš’™—J˜˜?Jšœ™šœžœŸ˜JšœŸ˜ JšœŸ ˜JšœŸ˜#JšœŸ/˜FJšœŸR˜cJšœŸ'˜,JšœŸ2™GJšœŸ ˜JšœŸ ˜Jšœ Ÿ ˜JšœŸ ˜Jšœ?Ÿ˜GJ˜—Jšœ ™ šœžœŸ˜JšœŸ˜ JšœŸ ˜JšœŸ˜!JšœŸ-˜KJšœŸI˜ZJšœŸ'˜,JšœŸ™%JšœŸ ˜JšœŸ ˜Jšœ Ÿ ˜JšœŸ ˜JšœCŸ˜KJ˜—J™šœžœŸ˜JšœŸ˜ JšœŸ ˜JšœŸ˜!JšœŸ/˜JJšœŸ?˜PJšœŸ'˜,JšœŸ™&JšœŸ ˜JšœŸ ˜Jšœ Ÿ ˜JšœŸ ˜JšœOŸ˜WJ˜—J™$šœžœŸ˜JšœŸ˜ JšœŸ ˜JšœŸ˜!JšœŸ˜%JšœŸ?˜PJšœŸ˜JšœŸ™&JšœŸ ˜JšœŸ ˜Jšœ Ÿ ˜JšœŸ ˜Jšœ?Ÿ˜GJ˜—J˜—J˜šœ žœžœ˜2J™"J˜ Jšœžœ˜Jšœžœ˜J˜ J˜'Jšœ˜—Jšœžœ˜ J˜šœ žœžœ˜2J™!J˜ Jšœžœ˜Jšœžœ˜J˜J˜(J˜—J˜šœžœžœ˜4J™-J˜ Jšœžœ˜Jšœžœ˜J˜ J˜+J˜—Jšœžœ˜$J˜šœžœžœ˜4J™-J˜Jšœžœ˜Jšœžœ˜J˜ J˜+J˜J˜—Jš œ žœžœžœžœ+˜MJš œ žœžœžœžœ1˜TJ˜—™ J˜Jšœ žœ˜,Jšœžœ˜&šœžœ žœ˜)JšœjŸœ˜‚—šœžœžœ žœ˜4JšœŸ ˜'Jšœ4Ÿ ˜=JšœŸ ˜'Jšœ7Ÿ ˜@JšœŸ˜ J˜J˜—šœ žœ˜JšœŸ˜JšœŸR˜WJšœŸM˜\Jšœ ŸD˜NJšœ ŸbΠckŸ£Ÿ˜tJšœŸ4˜9Jšœ ŸQ˜[JšœŸ+˜0Jšœ Ÿ4˜>JšœŸ˜Jšœ ŸD˜NJšœ ŸT˜^Jšœ Ÿ˜Jšœ Ÿ˜Jšœ Ÿ˜ JšœŸ˜"JšœŸj˜oJšœŸh˜mJšœŸH˜JJ˜J˜—š ‘ Πfk‘ €‘€‘ €‘ ˜;Jš‘U™UJš‘MΠcf ˜ZJš‘M₯ ˜ZJš‘M₯˜]Jš‘M₯˜cJš‘M₯˜`Jš‘M₯˜cJš‘M₯˜^Jš‘M₯˜\Jš‘M₯˜`Jš‘M₯˜]Jš‘M₯˜]Jš‘M₯˜^Jš‘M₯˜^Jš‘M₯˜^Jš‘M₯˜_J˜—J˜J™J˜#šœG˜GJ˜•—J˜J˜+šœ˜J˜ΓJ˜—J˜+šœ„˜„J˜Ϋ—J˜J˜,šœ%˜%Jšœp˜pJ˜ŽJ˜—J˜šœ%˜%Jšœo˜oJ˜Ν—J˜J˜šœ%˜%Jšœ ˜ J˜iJ˜——™$J˜J˜(Jšœ žœžœ˜DJ˜J˜(Jšœ žœžœ˜DJ˜J˜"Jšœ žœžœ˜8J˜šœžœžœ˜J˜J˜—J˜šœžœžœ˜ Jšœ ž˜J˜J˜—šœ!žœ˜*J˜Jšœ˜—JšœY˜YJ˜—™'K™KšœPΟrœ¦z™ΰ—K™™'K™)Kšœ ¦ ™—™(K™Kšœ ¦)™5—™1Kšœ ¦Wœ¦œ¦#™Μ—™2Kš œ ¦œ¦œ¦œ¦œ¦#œ™ΔKšœ ¦œ¦‰œ™Ω—™2K™Kš œ ¦œC¦ œ¦œ¦œ™½—™2K™OKšœ ¦1œ¦œ¦œ™ž—™2K™9Kšœ ¦ œ™/—™2K™TKšœ ¦ ™—™4K™Kš œ ¦:œ¦œ¦œ¦ œ¦™Ί—™4K™αKš œ ¦Rœ¦œ¦œ¦ œ¦™σ—™5K™/——…—yXΈE