DIRECTORY
BasicTime USING [ Now, nullGMT, OutOfRange, Update ],
Commander USING [ CommandProc, Register ],
FinchSmarts,
IO,
Lark USING [ KeyTable, SHHH ],
LupineRuntime USING [ BindingError ],
NamesGV USING [ GVGetAttribute ],
NamesGVImpExp USING [ GVImport, UnGVImport ],
NamesRPC USING [ StartConversation ],
Nice,

PrincOpsUtils USING [ IsBound ],
Process USING [ Detach, SecondsToTicks, SetTimeout, Ticks ],
RefQ USING [ Dequeue, Enqueue, Map, MapType, Queue ],
Rope,
RPC USING [ AuthenticateFailed, CallFailed, EncryptionKey, ImportFailed, VersionRange ],
RuntimeError USING [ UNCAUGHT ],
Synthesizer USING [ BreakText ],
ThParty	USING [ Advance, Alert, ConversationsForParty, CreateParty, Deregister, DescribeInterval, DescribeParty, GetNumbersForRName, GetParty, GetPartyFromNumber, OtherParty, Register, RegisterKey, SetIntervals, SetProse ],
ThPartyRpcControl,
Thrush USING[
CallUrgency, ConversationHandle, ConvEvent, Disposition, EncryptionKey, IntervalSpec, IntervalSpecs, IntervalSpecBody, IntID, IntSpecType, NB, NetAddress, none, nullConvHandle, nullHandle, nullKey, nullTune, PartyHandle, ProseSpec, ProseSpecs, ProseSpecBody, Reason, ROPE, SmartsHandle, StateID, StateInConv, ThHandle, Tune, unencrypted, VoiceDirection, VoiceInterval ],
ThSmarts,
ThSmartsRpcControl,
ThVersions USING [ GetThrushVR, FinchVersion, FinchVR ],
UserProfile USING [ Token],
VoiceUtils USING [ CurrentPasskey, CurrentRName, InstanceFromNetAddress, MakeRName, NetAddress, NetAddressFromRope, OwnNetAddress, Problem, Report ]
;

FinchSmartsImpl: CEDAR MONITOR
IMPORTS BasicTime, Commander, IO, FinchSmarts, LupineRuntime, NamesGV, NamesGVImpExp, NamesRPC, Nice, PrincOpsUtils, Process, RefQ, RPC, Rope, RuntimeError, Synthesizer, ThParty, ThPartyRpcControl, ThSmartsRpcControl, ThVersions, UserProfile, VoiceUtils
EXPORTS FinchSmarts, ThSmarts = {
OPEN IO;


CallUrgency: TYPE = Thrush.CallUrgency;
ConvDesc: TYPE = FinchSmarts.ConvDesc;
ConversationHandle: TYPE = Thrush.ConversationHandle;
nullConvHandle: ConversationHandle = Thrush.nullConvHandle;
Disposition: TYPE = Thrush.Disposition;
FinchInfo: TYPE = FinchSmarts.FinchInfo;
IntervalSpec: TYPE = Thrush.IntervalSpec;
IntervalSpecs: TYPE = Thrush.IntervalSpecs;
ProseSpec: TYPE = Thrush.ProseSpec;
ProseSpecs: TYPE = Thrush.ProseSpecs;
NB: TYPE = Thrush.NB;
none: SHHH = Thrush.none;
nullHandle: Thrush.ThHandle = Thrush.nullHandle;
PartyHandle: TYPE = Thrush.PartyHandle;
Reason: TYPE = Thrush.Reason;
ROPE: TYPE = Thrush.ROPE;
SHHH: TYPE = Lark.SHHH;
SmartsHandle: TYPE = Thrush.SmartsHandle;
StateInConv: TYPE = Thrush.StateInConv;

PD: TYPE = RECORD [
doReports: BOOL_FALSE,
doNice: BOOL_FALSE,
timeoutNoAction: INTEGER _ 30,
noActionTicks: Process.Ticks _ Process.SecondsToTicks[30],
timeoutJayConnect: INTEGER _ 1,
noJayTicks: Process.Ticks _ Process.SecondsToTicks[1],
encryptionRequested: BOOLEAN_TRUE,
interfacesAreImported: BOOLEAN_FALSE,
smartsIsExported: BOOLEAN_FALSE,
waitsForConnect: NAT_6,
queueIt: BOOL_FALSE,
finchOn: BOOLEAN_FALSE,
maxProseLength: INT_1000,  -- ideally, should be a multiple of the LarkOut packet length
intvReq: CARDINAL _ 177777B
];

info: FinchInfo;
pd: REF PD _ NEW[PD_[]];

stopIntervalSpec: Thrush.IntervalSpec = NEW[Thrush.IntervalSpecBody_[
interval: [length: 0], direction: play, queueIt: FALSE] ];

stopProseSpec: Thrush.ProseSpec = NEW[Thrush.ProseSpecBody_[
prose: "", direction: play, queueIt: FALSE] ];

resetProseSpec: Thrush.ProseSpec = NEW[Thrush.ProseSpecBody_[
prose: "cP;z:cp0\\P;z:pp0\\P;z:ra180\\P;z:np\\", direction: record, queueIt: FALSE] ];

dectalkEndSpec: Thrush.ProseSpec = NEW[Thrush.ProseSpecBody_[
prose: " \033P;z+\033\\", direction: play, queueIt: TRUE] ]; -- paragraph pause

Report: PROC[what: ROPE] = {
IF NOT pd.doReports THEN RETURN;
VoiceUtils.Report[what, $Finch];
};

BeNice: PROC[r: REF, d: INT] = {
IF NOT pd.doNice THEN RETURN;
Nice.BeNice[r, d, $Finch, NIL];
};

Progress: PUBLIC ENTRY PROC[
shh: SHHH,
smartsID: Thrush.SmartsHandle,
event: Thrush.ConvEvent,
yourParty: BOOL,
latestEvent: BOOL,
informationOnly: BOOL
] RETURNS [ d: Thrush.Disposition ] = {
ENABLE UNWIND => NULL;
cDesc: ConvDesc;
IF info=NIL THEN RETURN[pass];
d_pass;

IF pd.doReports THEN Report[
Rope.Concat[
IO.PutFR["---- FnProg: %g(%d) %g %g yr=%g ",
PutFTime[event.credentials.convID], int[event.credentials.stateID],
refAny[NEW[StateInConv_event.state]], rope[info.myRName], bool[yourParty]],
IO.PutFR["lt=%g in=%g, pr=%g, ky=%g\n",
bool[latestEvent], bool[event.intervalSpecs#NIL], bool[event.proseSpecs#NIL], bool[event.keyTable#NIL]]]];

cDesc _ GetConv[event.credentials.convID, FALSE];
IF event.credentials.stateID <= cDesc.cState.credentials.stateID THEN RETURN[pass]; -- Old news!
cDesc.cState.credentials.smartsID _ smartsID;
cDesc.cState.credentials.stateID _ event.credentials.stateID;

IF event.keyTable#NIL THEN {
cDesc.cState.keyTable _ event.keyTable; cDesc.newKeys_TRUE; };
IF event.intervalSpecs#NIL THEN ReportIntervals[cDesc, event];
IF event.proseSpecs#NIL THEN ReportProses[cDesc, event];
IF event.address#NIL THEN { cDesc.cState.address_event.address; cDesc.newAddress_TRUE; };
IF yourParty THEN {

Other: PROC={
oD: ROPE;
IF (~latestEvent) OR cDesc.otherPartyID#nullHandle THEN RETURN;
[,cDesc.otherPartyID, oD, cDesc.conference] _
ThParty.OtherParty[shhh: info.shh, credentials: cDesc.cState.credentials];
IF oD#NIL THEN cDesc.otherPartyDesc _ oD;
};

cDesc.descValid _ TRUE;
cDesc.cState.credentials.partyID _ event.credentials.partyID;
cDesc.cState.state _ event.state;
cDesc.cState.comment _ event.comment;
cDesc.cState.reason _ event.reason;
IF event.spec#NIL THEN { cDesc.cState.spec _ event.spec; cDesc.newSpec_TRUE; };
IF event.comment#NIL THEN cDesc.cState.comment _ event.comment;
IF event.urgency#normal THEN cDesc.cState.urgency _ event.urgency;
IF event.alertKind#standard THEN cDesc.cState.alertKind _ event.alertKind;
SELECT event.state FROM
reserved, parsing => cDesc.originator _ us;
initiating => { cDesc.originator _ us; Other[]; };
pending => { cDesc.originator _ them; Other[]; };
maybe, ringing, active, canActivate, inactive => Other[];
ENDCASE;
};

BeNice[event, 4];
BeNice[cDesc, 6];
cDesc.newEvent_TRUE;
IF latestEvent THEN Apprise[info]; -- Wait for the last report to wake process.
};

Supervise: PUBLIC ENTRY PROC[info: FinchInfo ] = {
problem: ROPE_NIL;
TRUSTED { Process.SetTimeout[@info.thAction, pd.noActionTicks]; };
IF info.apprise THEN DO
ENABLE {
UNWIND => NULL;
RuntimeError.UNCAUGHT => Problem["Unknown Finch Smarts Supervisor Failure"];
};
nb: NB_success;
trans: Transition;
info.apprise _ FALSE;
FOR conversations: RefQ.Queue _ info.conversations, conversations.rest WHILE conversations#NIL DO
cDesc: ConvDesc = NARROW[conversations.first];
stateNow: StateInConv = cDesc.cState.state;
newEvent: BOOL=cDesc.newEvent;
ours: BOOL _ (info.currentConvID = cDesc.cState.credentials.convID);
cDesc.newEvent_FALSE; -- For things that must be done once-only per new state.

IF newEvent OR stateNow#idle THEN {
IF pd.doReports THEN Report[
Rope.Concat[
IO.PutFR["**** FnSup: %g(%d) %g %g->%g",
PutFTime[cDesc.cState.credentials.convID], int[cDesc.cState.credentials.stateID],
rope[info.myRName], refAny[NEW[StateInConv_stateNow]], refAny[NEW[StateInConv_cDesc.desiredState]]],
IO.PutFR[" %g%g\n",
refAny[NEW[Transition_transForStates[stateNow][cDesc.desiredState]]],
rope[IF ours THEN " (ours)" ELSE ""]]]];
BeNice[cDesc, 6];
};
IF NOT cDesc.descValid THEN LOOP;
SELECT stateNow FROM
idle => IF ours THEN info.currentConvID _ nullConvHandle;
parsing, reserved, initiating, maybe, ringing, canActivate, active, inactive => {
ours_TRUE;
IF cDesc.ultimateState<active THEN cDesc.ultimateState _ stateNow;
info.currentConvID _ cDesc.cState.credentials.convID;
};
pending => cDesc.ultimateState _ pending;
any => NULL;
ENDCASE => NULL;
SELECT (trans_transForStates[stateNow][cDesc.desiredState]) FROM
noop => NULL;
elim => {
cDesc.requestedIntervals_cDesc.pendingIntervals_NIL;
cDesc.bluejayConnection _ cDesc.proseConnection _ FALSE;
cDesc.requestedProses_cDesc.pendingProses_NIL;
};
alrt => { -- placing call, or reserving conversation
convID: ConversationHandle;
IF NOT ours THEN Problem["What to do in a race?"];
IF cDesc.desiredState#reserved THEN cDesc.weOriginated _ TRUE;
[nb, convID] _ ThParty.Alert [
credentials: cDesc.cState.credentials,
calledPartyID: cDesc.desiredPartyID,
state: IF cDesc.desiredState=reserved THEN reserved ELSE initiating,
reason: cDesc.desiredReason,
comment: cDesc.desiredComment
];
IF nb=success THEN {
cDesc.cState.credentials.convID _ info.currentConvID _ convID;
ours_TRUE;
};
};
idle, actv => -- Simple transitions
nb _ ThParty.Advance [
shhh: info.shh,
credentials: cDesc.cState.credentials,
state: cDesc.desiredState,
reason: cDesc.desiredReason,
comment: cDesc.desiredComment
];
spvs => {
IF cDesc.pendingIntervals#NIL THEN {
nb _ ThParty.SetIntervals[
shhh: info.shh,
credentials: cDesc.cState.credentials,
intervalSpecs: cDesc.pendingIntervals
];
IF nb=success THEN cDesc.pendingIntervals_NIL;
};
IF cDesc.pendingProses#NIL THEN {
nextPSL, prevPSL: ProseSpecs _ NIL;
stateID: Thrush.StateID=cDesc.cState.credentials.stateID+1;
reqID: CARDINAL _ 177777B;
textLen: INT _ 0;
FOR pSL: ProseSpecs _ cDesc.pendingProses, pSL.rest WHILE pSL#NIL DO
IF (textLen _ textLen+pSL.first.prose.Length[]) <= pd.maxProseLength
THEN prevPSL _ pSL
ELSE {
nextPSL _ pSL;
prevPSL.rest _ NIL;
EXIT;
};
ENDLOOP;
nb _ ThParty.SetProse[
shhh: info.shh,
credentials: cDesc.cState.credentials,
proseSpecs: cDesc.pendingProses
];
prevPSL.rest _ nextPSL;  -- put the list back together so that cDesc.requestedProses is still connected
IF nb=success THEN {
cDesc.pendingProses _ nextPSL;
IF ~cDesc.proseConnection THEN cDesc.requestedProses _ NIL;
};
};
};
invl => {
Problem["FinchSmarts: Invalid state transition request."];
info.apprise_TRUE;
cDesc.desiredState _ idle;
cDesc.desiredReason _ error;
cDesc.desiredComment _ "Invalid state transition";
};
ntiy => {
Problem["FinchSmarts: State transition not yet implemented."];
info.apprise_TRUE;
cDesc.desiredState _ idle;
cDesc.desiredReason _ error;
cDesc.desiredComment _ "Unimplemented state transition";
};
ENDCASE => ERROR;

IF nb#success AND pd.doReports THEN
Report[IO.PutFR["  ** Results: nb=%g\n", refAny[NEW[Thrush.NB_nb]]]];
SELECT nb FROM
success, stateMismatch => NULL;
noSuchParty2 => -- Have to get to error tone here.  No such party.
Complain[info, cDesc, notFound, "Called party not found"];
narcissism => -- Have to get to error tone here.  No such party.
Complain[info, cDesc, notFound, "Attempt to call self rejected on philosophical grounds"];
partyNotEnabled => {
info.ReportConversationState[noSuchSmarts, cDesc, "Your Etherphone is not connected to the telephone server"];
};
invalidTransition, convNotActive, convStillActive => {
comment: ROPE="Party-level detected invalid state transition request";
Problem[comment];
Complain[info, cDesc, error, comment];
};
notInConv, noSuchConv => { -- Complain, zap, go idle and repeat.
comment: ROPE="NotInConv or NoSuchConv";
Problem[comment];
IF ours THEN info.currentConvID _ nullConvHandle;
cDesc.cState.credentials.convID _ nullConvHandle;
cDesc.cState.credentials.stateID _ 0;
Complain[info, cDesc, error, comment];
};
noSuchParty, noSuchSmarts => { -- Complain, deregister, we gone! Needs tuning.
problem _ "NoSuchParty or NoSuchSmarts reported, must try to go away";
GOTO Failing;
};
ENDCASE => ERROR;
IF newEvent THEN info.ReportConversationState[success, cDesc, NIL];
FOR iSs: IntervalSpecs _ cDesc.requestedIntervals, iSs.rest WHILE iSs#NIL DO
IF iSs.first.type=finished AND iSs.first.changeNoted THEN
cDesc.requestedIntervals _ iSs.rest
ELSE EXIT;
ENDLOOP;
FOR pSs: ProseSpecs _ cDesc.requestedProses, pSs.rest WHILE pSs#NIL DO
IF pSs.first.type=finished AND pSs.first.changeNoted THEN
cDesc.requestedProses _ pSs.rest
ELSE EXIT;
ENDLOOP;
IF stateNow=idle THEN {
info.conversations _ RefQ.Dequeue[info.conversations, conversations];
cDesc.clientData _ NIL;
};
ENDLOOP;
IF info.conversations = NIL THEN EXIT;
IF NOT info.apprise THEN WAIT info.thAction;
IF info.conversations = NIL THEN EXIT;
REPEAT Failing => UninitFinchSmarts[problem]; -- now Failed
ENDLOOP;
info.thProcess _ NIL;
};

GetRname: PUBLIC PROC[partyID: Thrush.PartyHandle] RETURNS [rName: ROPE] = {
RETURN[IF info=NIL THEN NIL ELSE ThParty.DescribeParty[shh: info.shh, partyID: partyID]];
};

DisconnectCall: PUBLIC ENTRY PROC[
convID: Thrush.ConversationHandle, -- not used yet
reason: Thrush.Reason_terminating,
comment: ROPE_NIL] = {
ENABLE UNWIND => NULL;
cDesc: ConvDesc; state: StateInConv;
IF NOT(([,cDesc, state]_FinchOn[]).on) THEN RETURN;
cDesc.bluejayConnection _ cDesc.proseConnection _ FALSE;
SELECT state FROM
idle, any => {
info.ReportConversationState[convNotActive, NIL, "No conversation to disconnect"];
RETURN;
};
ringing, pending => IF reason=terminating THEN reason _ busy;
ENDCASE;
Request[info, cDesc, idle, reason, comment];
};

AnswerCall: PUBLIC ENTRY PROC[convID: Thrush.ConversationHandle -- not used yet -- ] = {
ENABLE UNWIND => NULL;
cDesc: ConvDesc; state: StateInConv;
IF NOT(([,cDesc, state]_FinchOn[]).on) THEN RETURN;
SELECT state FROM
ringing, pending => NULL;
ENDCASE=>RETURN;
Request[info, cDesc, active];
};

PlaceCall: PUBLIC ENTRY PROC [
convID: Thrush.ConversationHandle, -- not used yet --
rName: ROPE, -- rName or description
number: ROPE, -- telephone number, if present
urgency: Thrush.CallUrgency_normal,
useNumber: BOOL_FALSE] = {
ENABLE { UNWIND=>NULL; RPC.CallFailed => { UninitFinchSmarts["Communication Failure"]; CONTINUE; }; };
calledPartyID: PartyHandle;
fullRName: ROPE;
IF NOT (FinchOn[].on) THEN RETURN;
calledPartyID _ SELECT TRUE FROM
~useNumber AND
(calledPartyID _ ThParty.GetParty[shh: info.shh, partyID: info.partyID, rName: rName]) #nullHandle =>
calledPartyID,
number#NIL =>
ThParty.GetPartyFromNumber[shh: info.shh, partyID: info.partyID, phoneNumber: number, description: rName, trunkOK: TRUE],
rName=NIL OR useNumber => nullHandle,
([fullRName, number,] _ ThParty.GetNumbersForRName[shh: info.shh, rName: rName]).number # NIL =>
ThParty.GetPartyFromNumber[
shh: info.shh, partyID: info.partyID, phoneNumber: number,
description: fullRName, trunkOK: TRUE],
ENDCASE => nullHandle;
IF calledPartyID = nullHandle THEN {
info.ReportConversationState[noSuchParty2, NIL,
IF rName=NIL THEN "You did not supply a call destination"
ELSE "No telephone number could be found for called party"];
};
[]_Connect[calledPartyID, FALSE, FALSE, urgency];
};

RecordTune: PUBLIC ENTRY PROC [
useTune: Thrush.Tune,
useInterval: Thrush.VoiceInterval,
queueIt: BOOL_FALSE
]
RETURNS[
reason: FinchSmarts.RecordReason_hopeless,
tune: Thrush.Tune_Thrush.nullTune,
interval: Thrush.VoiceInterval_[],
key: Thrush.EncryptionKey_Thrush.nullKey
] = {
ENABLE UNWIND=>NULL;
ourSpec: Thrush.IntervalSpec;
cDesc: ConvDesc; state: StateInConv;
started: BOOL_FALSE;
IF NOT (([,cDesc,state]_JayConnection[TRUE]).jayOpen) THEN RETURN;
ourSpec _ NEW[Thrush.IntervalSpecBody _ [
type: request, direction: record, queueIt: queueIt,
tune: useTune, interval: useInterval, keyIndex: 1 
]];
EnqueueIntervals[cDesc, LIST[ourSpec]];
started _ WaitForStartOrFail[cDesc, ourSpec];
state _ cDesc.cState.state;

IF ~started OR cDesc.cState.keyTable=NIL THEN {
IF state#idle THEN Complain[info, cDesc, error, "Voice server connection failed"];
RETURN[hopeless, Thrush.nullTune, , ];
};
WHILE cDesc.cState.state#idle AND ourSpec.type#finished DO
WAIT info.thAction;
ENDLOOP;
RETURN[ok, ourSpec.tune, ourSpec.interval, cDesc.cState.keyTable[ourSpec.keyIndex]];
};

WaitForStartOrFail: INTERNAL PROC[cDesc: ConvDesc, spec: Thrush.IntervalSpec]
RETURNS[started: BOOL_FALSE] = {
ENABLE UNWIND => NULL;
TRUSTED { Process.SetTimeout[@info.thAction, pd.noJayTicks]; };
FOR i: NAT IN [0..pd.waitsForConnect) DO
WAIT info.thAction; -- <<The supervisor condition vbl; will this work?>>
IF cDesc.cState.state=idle OR (started_(spec.type#request)) THEN EXIT;
ENDLOOP;
TRUSTED { Process.SetTimeout[@info.thAction, pd.noActionTicks]; };
};

StopTune: PUBLIC ENTRY PROC [reason: FinchSmarts.RecordReason_ok] = {
ENABLE UNWIND=>NULL;
cDesc: ConvDesc;
IF NOT (([,cDesc,]_JayConnection[FALSE]).jayOpen) THEN RETURN; -- Stop only if started
EnqueueIntervals[cDesc, LIST[NEW[Thrush.IntervalSpecBody_stopIntervalSpec^]]];
}; 

StopSpeech: PUBLIC ENTRY PROC [reason: FinchSmarts.RecordReason_ok] = {
ENABLE UNWIND=>NULL;
cDesc: ConvDesc;
IF NOT (([,cDesc,]_ProseConnection[FALSE]).proseOpen) THEN RETURN; -- Stop only if started
ClearPendingProses[cDesc];
EnqueueProses[cDesc, LIST[NEW[Thrush.ProseSpecBody_stopProseSpec^]]];
}; 

ResetProse: PUBLIC ENTRY PROC [reason: FinchSmarts.RecordReason_ok] = {
ENABLE UNWIND=>NULL;
cDesc: ConvDesc;
IF NOT (([,cDesc,]_ProseConnection[FALSE]).proseOpen) THEN RETURN; -- Stop only if started
ClearPendingProses[cDesc];
EnqueueProses[cDesc, LIST[NEW[Thrush.ProseSpecBody_resetProseSpec^]]];
}; 

PlaybackTune: PUBLIC ENTRY PROC [
tune: Thrush.Tune,
interval: Thrush.VoiceInterval,
key: Thrush.EncryptionKey,
queueIt: BOOL_FALSE,
failOK: BOOL, -- playing is optional; leave connection open if tune doesn't exist.
wait: BOOL_FALSE
] RETURNS[ started: BOOL_FALSE ] = { -- FALSE if failed or if didn't wait to find out
ENABLE UNWIND=>NULL;

cDesc: ConvDesc; state: StateInConv;
nb: NB; keyIndex: [0..17B];
exists: BOOL;
specs: Thrush.IntervalSpecs;
spec: Thrush.IntervalSpec;
IF tune<=Thrush.nullTune THEN {
info.ReportConversationState[convNotActive, NIL, "No such tune"]; RETURN; }; -- UGH!
IF NOT (([,cDesc,state]_JayConnection[TRUE]).jayOpen) THEN RETURN;
[nb, keyIndex] _
ThParty.RegisterKey[shh: info.shh, credentials: cDesc.cState.credentials, key: key];
IF nb#success AND nb#stateMismatch THEN {
IF ~failOK THEN Complain[info, cDesc, error, "Could not encode encryption key"];
RETURN;
};
spec _ NEW[Thrush.IntervalSpecBody _ [ tune: tune, interval: interval, direction: play ] ];
[, exists, specs] _
ThParty.DescribeInterval[
shhh: info.shh, credentials: cDesc.cState.credentials,
targetInterval: spec, minSilence: LAST[INT]]; -- Just trim off surrounding silences.
IF ~exists THEN {
IF ~failOK THEN Complain[info, cDesc, error, "Could not play utterance"];
RETURN;
};
IF specs=NIL THEN specs _ LIST[spec];
spec _ specs.first;
FOR sL: Thrush.IntervalSpecs _ specs, sL.rest WHILE sL#NIL DO
IF sL#specs THEN spec.interval.length _
(sL.first.interval.start+sL.first.interval.length) - spec.interval.start;
ENDLOOP;
spec.keyIndex _ keyIndex; spec.type _ request; spec.direction _ play; spec.queueIt _ queueIt;
EnqueueIntervals[cDesc, specs ];
IF wait THEN started _ WaitForStartOrFail[cDesc, spec];
};

defaultTranslateProc: FinchSmarts.ProseTranslateProc_NIL;
RegisterTranslateProc: PUBLIC PROC [translate: FinchSmarts.ProseTranslateProc_NIL] ~ {
defaultTranslateProc _ translate;
};

TextToSpeech: PUBLIC ENTRY PROC [
text: Rope.ROPE, queueIt: BOOL_TRUE, 
proseTranslateProc: FinchSmarts.ProseTranslateProc_NIL] 
RETURNS [reason: FinchSmarts.RecordReason_ok] = {
ENABLE UNWIND => NULL;
ourSpec: Thrush.ProseSpec;
cDesc: ConvDesc; state: StateInConv;
IF proseTranslateProc#NIL THEN text _ proseTranslateProc[text]
ELSE IF defaultTranslateProc#NIL THEN text _ defaultTranslateProc[text];
IF NOT (([,cDesc,state]_ProseConnection[TRUE]).proseOpen) THEN
RETURN[hopeless];
IF ~queueIt THEN ClearPendingProses[cDesc];  -- need to generate reports??
WHILE text.Length[] > pd.maxProseLength DO
proseText: Rope.ROPE _ NIL;
[packet: proseText, remainder: text] _ Synthesizer.BreakText[text, pd.maxProseLength];
ourSpec _ NEW[Thrush.ProseSpecBody _ [
type: request, direction: play, queueIt: queueIt, prose: proseText
]];
EnqueueProses[cDesc, LIST[ourSpec]];
queueIt _ TRUE;
ENDLOOP;
ourSpec _ NEW[Thrush.ProseSpecBody _ [
type: request, direction: play, queueIt: queueIt, prose: text
]];
EnqueueProses[cDesc, LIST[ourSpec, dectalkEndSpec]];
};


InitFinchSmarts: PUBLIC PROC [
thrushInstance: Thrush.ROPE_NIL,
ReportSystemState: PROC[ on: BOOL ],
ReportConversationState: PROC[ nb: NB, cDesc: ConvDesc, remark: Rope.ROPE ]
] = {
problem: ROPE_NIL; {
ENABLE RPC.CallFailed => { problem _ "Communication Failure"; GOTO InitFailed; };
partyID: Thrush.PartyHandle;
smartsID: Thrush.SmartsHandle;
thVR: RPC.VersionRange = ThVersions.GetThrushVR;
problem: Thrush.ROPE _ NIL;
namesGVInstance: Thrush.ROPE_NIL;
hostHint: VoiceUtils.NetAddress;
smartsNetAddress: Thrush.NetAddress = VoiceUtils.OwnNetAddress[];

UninitFinchSmarts[NIL];

info _ NEW[FinchSmarts.FinchInfoBody]; -- Dump any old one!
info.conversations _ NIL;
info.thProcess _ NIL;
info.currentConvID _ nullConvHandle;
info.apprise _ FALSE;
info.ReportSystemState_ReportSystemState;
info.ReportConversationState_ReportConversationState;
thrushInstance _ VoiceUtils.MakeRName[style: rName, name:
IF thrushInstance#NIL THEN thrushInstance
ELSE UserProfile.Token[key: "ThrushClientServerInstance", default: "Strowger.Lark"]];
info.myName _ [
type: "ThSmarts.Lark",
instance: VoiceUtils.InstanceFromNetAddress[netAddress: smartsNetAddress, suffix: "0"],
version: ThVersions.FinchVR];
info.myRName _ VoiceUtils.CurrentRName[];
info.myPassword _ VoiceUtils.CurrentPasskey[];
ThSmartsRpcControl.ExportInterface[
interfaceName: info.myName,
user: info.myRName,
password: info.myPassword];
pd.smartsIsExported_TRUE;

namesGVInstance _ UserProfile.Token[key: "NamesGVInstance", default: "Strowger.lark"];
IF ~(PrincOpsUtils.IsBound[LOOPHOLE[NamesGVImpExp.GVImport]] AND NamesGVImpExp.GVImport[namesGVInstance]) THEN {
problem _ "Couldn't import Grapevine Package"; GOTO InitFailed; };

info.shh _ IF NOT pd.encryptionRequested THEN Thrush.unencrypted
ELSE NamesRPC.StartConversation [
caller: info.myRName,
callee: thrushInstance,
key:	info.myPassword,
level:	--<<ECB>>--CBCCheck !
RPC.AuthenticateFailed=> { problem_"Could not authenticate"; GOTO InitFailed}];

hostHint _
VoiceUtils.NetAddressFromRope[NamesGV.GVGetAttribute[thrushInstance, $connect, NIL]];

ThPartyRpcControl.ImportInterface[
interfaceName: [type: "ThParty.Lark", instance: thrushInstance, version: thVR],
hostHint: hostHint! RPC.ImportFailed=> {
IF why=wrongVersion THEN
problem _ IO.PutFR["Finch version %d too old; import failed",
card[ThVersions.FinchVersion]];
GOTO InitFailed;
}];
pd.interfacesAreImported_TRUE;

partyID_ThParty.CreateParty[shh: info.shh, type: individual, rName: info.myRName];
IF partyID=Thrush.nullHandle THEN { problem_"Can't register with server"; GOTO InitFailed; };
smartsID_ThParty.Register[
shh: info.shh, partyID: partyID, interface: NEW[ThSmartsRpcControl.InterfaceName_info.myName],
properties: [x: manager[netAddress: [smartsNetAddress.net, smartsNetAddress.host]]]] ;

IF smartsID=Thrush.nullHandle THEN { problem_"Can't register with server"; GOTO InitFailed; }; -- <<try to delete the Party?>>
info.smartsID _ smartsID;
info.partyID _ partyID;
ThParty.ConversationsForParty[shh: info.shh, partyID: partyID];
pd.finchOn_TRUE;
info.ReportSystemState[pd.finchOn];
EXITS
InitFailed => UninitFinchSmarts[problem];
};};

UninitFinchSmarts: PUBLIC PROC[problem: ROPE_NIL] = {
ENABLE RPC.CallFailed => GOTO Failed;
IF problem#NIL THEN Problem[problem];
IF info#NIL THEN {
IF pd.finchOn AND info.partyID#nullHandle AND info.smartsID#nullHandle THEN
ThParty.Deregister[info.shh, info.smartsID!RPC.CallFailed=>CONTINUE];
info.shh_none;
info.ReportSystemState[FALSE];
{
ClearConvs: RefQ.MapType = {
cDesc: ConvDesc=NARROW[subqueue.first];
cDesc.clientData _ NIL;
};
[]_RefQ.Map[info.conversations, ClearConvs];
info.conversations _ NIL;
};
};
pd.finchOn_FALSE;
IF PrincOpsUtils.IsBound[LOOPHOLE[NamesGVImpExp.UnGVImport]] THEN
NamesGVImpExp.UnGVImport[];
pd.interfacesAreImported_FALSE;
IF pd.smartsIsExported THEN
ThSmartsRpcControl.UnexportInterface[!LupineRuntime.BindingError=>CONTINUE];
pd.smartsIsExported_FALSE;
EXITS
Failed => pd.interfacesAreImported _ pd.smartsIsExported _ FALSE;
};

FinchIsRunning: PUBLIC PROC RETURNS [finchIsRunning: BOOL] = { RETURN[pd.finchOn]; }; 


GetConv: PUBLIC INTERNAL PROC[convID: ConversationHandle, validIfNew: BOOL
] RETURNS [ cDesc: ConvDesc_NIL ] = --INLINE-- {
IsConv: RefQ.MapType = {
cDesc _ NARROW[subqueue.first];
IF cDesc.cState.credentials.convID = convID THEN RETURN[TRUE];
};
IF convID#nullConvHandle AND RefQ.Map[info.conversations, IsConv] THEN RETURN;
cDesc _ NEW[FinchSmarts.ConvDescBody_[]];
cDesc.otherPartyDesc _ "unknown party";
cDesc.descValid _ validIfNew;
cDesc.startTime _ BasicTime.Now[];
cDesc.desiredPartyID _ nullHandle;
cDesc.cState.credentials _ [
convID: convID, smartsID: info.smartsID, partyID: info.partyID, stateID: 0];
info.conversations _ RefQ.Enqueue[info.conversations, cDesc];
IF pd.doReports THEN
Report[IO.PutFR["  ** NewConv %g %g, vl=%g\n", PutFTime[convID], rope[info.myRName], bool[validIfNew]]];
};

PutFTime: PROC[convID: ConversationHandle] RETURNS [IO.Value] = { 
ehsMemorialBool: BOOL_FALSE; -- wouldn't need if could return from catch phrase.
IF convID=nullConvHandle OR convID=BasicTime.nullGMT
THEN RETURN[rope["(not assigned)"]];
[]_BasicTime.Update[convID, 0!BasicTime.OutOfRange=> {
ehsMemorialBool_TRUE; CONTINUE; }];
IF ehsMemorialBool THEN RETURN[int[LOOPHOLE[convID, INT]]]
ELSE RETURN[time[convID]];
};

GetConvDesc: PUBLIC PROC[convID: ConversationHandle]RETURNS[cDesc: ConvDesc_NIL ] = {
IsConv: RefQ.MapType = {
cDesc _ NARROW[subqueue.first];
IF cDesc.cState.credentials.convID = convID THEN RETURN[TRUE];
};
IF convID=nullConvHandle THEN RETURN[NIL];
RETURN[IF RefQ.Map[info.conversations, IsConv] AND cDesc.descValid
THEN cDesc ELSE NIL];
};

GetCurrentConvID: PUBLIC PROC RETURNS [convID: ConversationHandle] = {
RETURN[info.currentConvID];
};


Apprise: PUBLIC INTERNAL PROC[info: FinchInfo] = --INLINE-- {
IF info.thProcess=NIL THEN
TRUSTED { Process.Detach[info.thProcess _ FORK Supervise[info]]; };
info.apprise _ TRUE;
BROADCAST info.thAction;
};

ReportIntervals: INTERNAL PROC[cDesc: ConvDesc, event: Thrush.ConvEvent] = {
FOR eSs: IntervalSpecs _ event.intervalSpecs, eSs.rest WHILE eSs#NIL DO
eS: IntervalSpec = eSs.first;
eSID: CARDINAL = eS.intID.reqID;
FOR rSs: IntervalSpecs _ cDesc.requestedIntervals, rSs.rest WHILE rSs#NIL DO
rS: IntervalSpec = rSs.first;
IF eSID # rS.intID.reqID THEN LOOP;
rS^ _ eS^; -- Update status.
IF rS.type=finished THEN -- Truncate requests
FOR fSs: IntervalSpecs _ cDesc.requestedIntervals, fSs.rest WHILE fSs#rSs DO
IF fSs.first.type # finished THEN {
fSs.first.type _ finished; fSs.first.changeNoted_FALSE; };
ENDLOOP;
EXIT;
ENDLOOP;
ENDLOOP;
};

ReportProses: INTERNAL PROC[cDesc: ConvDesc, event: Thrush.ConvEvent] = {
FOR eSs: ProseSpecs _ event.proseSpecs, eSs.rest WHILE eSs#NIL DO
eS: ProseSpec = eSs.first;
eSID: CARDINAL = eS.intID.reqID;
FOR rSs: ProseSpecs _ cDesc.requestedProses, rSs.rest WHILE rSs#cDesc.pendingProses AND rSs#NIL DO
rS: ProseSpec = rSs.first;
IF eSID # rS.intID.reqID THEN LOOP;
IF rS.type # eS.type THEN rS^ _ eS^; -- Update status.
IF rS.type=finished THEN -- Truncate requests
FOR fSs: ProseSpecs _ cDesc.requestedProses, fSs.rest WHILE fSs#rSs DO
IF fSs.first.type # finished THEN {
fSs.first.type _ finished; fSs.first.changeNoted_FALSE; };
ENDLOOP;
EXIT;
ENDLOOP;
ENDLOOP;
};

EnqueueIntervals: INTERNAL PROC[cDesc: ConvDesc, int: IntervalSpecs] =  {
FOR iSs: IntervalSpecs _ int, iSs.rest WHILE iSs#NIL DO
iSs.first.intID _ [0, pd.intvReq _ pd.intvReq+1];
ENDLOOP;
IF cDesc.pendingIntervals=NIL THEN cDesc.pendingIntervals_int;
IF cDesc.requestedIntervals=NIL THEN cDesc.requestedIntervals_int
ELSE FOR iSs: IntervalSpecs _ cDesc.requestedIntervals, iSs.rest WHILE iSs#NIL DO
IF iSs.rest=NIL THEN { iSs.rest _ int; EXIT; };
ENDLOOP;
Apprise[info];
};

EnqueueProses: INTERNAL PROC[cDesc: ConvDesc, prose: ProseSpecs] =  {
FOR pSs: ProseSpecs _ prose, pSs.rest WHILE pSs#NIL DO
pSs.first.intID _ [0, pd.intvReq _ pd.intvReq+1];
ENDLOOP;
IF cDesc.pendingProses=NIL THEN cDesc.pendingProses_prose;
IF cDesc.requestedProses=NIL THEN cDesc.requestedProses_prose
ELSE FOR pSs: ProseSpecs _ cDesc.requestedProses, pSs.rest WHILE pSs#NIL DO
IF pSs.rest=NIL THEN { pSs.rest _ prose; EXIT; };
ENDLOOP;
Apprise[info];
};

ClearPendingProses: INTERNAL PROC [cDesc: ConvDesc] ~ {
FOR pSs: ProseSpecs _ cDesc.requestedProses, pSs.rest WHILE pSs#NIL DO
IF pSs.rest=cDesc.pendingProses THEN { pSs.rest _ NIL; EXIT; };
ENDLOOP;
cDesc.pendingProses_NIL;
};

Complain: INTERNAL PROC[info: FinchInfo, cDesc: ConvDesc, reason: Reason_wontSay, comment: ROPE_NIL] = {
cDesc.desiredState _ IF cDesc.cState.state#any THEN idle ELSE reserved;
cDesc.desiredReason _ reason;
cDesc.desiredComment _ comment;
cDesc.desiredPartyID _ nullHandle;
cDesc.pendingIntervals _ NIL;
ClearPendingProses[cDesc];
Apprise[info]; -- BROADCAST is sometimes meaningless (running monitor.)
};

FinchOn: INTERNAL PROC RETURNS [
on: BOOL_FALSE, cDesc: ConvDesc_NIL, state: StateInConv_idle] = {
IF ~pd.finchOn OR info=NIL THEN {
VoiceUtils.Report["Your Finch is not running", $Finch]; RETURN; };
on_TRUE;
cDesc _ GetConvDesc[info.currentConvID];
state_IF cDesc=NIL THEN idle ELSE cDesc.cState.state;
};

Request: INTERNAL PROC[
info: FinchInfo,
cDesc: ConvDesc,
state: StateInConv,
reason: Reason_wontSay,
comment: ROPE_NIL
] = {
cDesc.desiredState _ state;
cDesc.desiredReason _ reason;
cDesc.desiredComment _ comment;
Apprise[info];
};

Connect: INTERNAL PROC [
calledPartyID: PartyHandle, bluejayConnection: BOOL, proseConnection: BOOL, urgency: Thrush.CallUrgency, waitForActive: BOOL_FALSE]
RETURNS [ cDesc: ConvDesc ] = {
state: StateInConv;
[,cDesc, state]_FinchOn[];
SELECT state FROM
idle => { cDesc _ GetConv[nullConvHandle, TRUE]; cDesc.cState.state_any; };
reserved => NULL;
ENDCASE => {
info.ReportConversationState[convStillActive, NIL, "Conversation already in progress"];
RETURN;
};
cDesc.bluejayConnection _ bluejayConnection;
cDesc.proseConnection _ proseConnection;
cDesc.desiredPartyID _ calledPartyID;
cDesc.pendingIntervals _ NIL;
ClearPendingProses[cDesc];
Request[info, cDesc, active];
IF ~waitForActive THEN RETURN;
FOR i: NAT IN [0..pd.waitsForConnect) DO
TRUSTED { Process.SetTimeout[@info.thAction, pd.noJayTicks]; };
WAIT info.thAction; -- <<The supervisor condition vbl; will this work?>>
TRUSTED { Process.SetTimeout[@info.thAction, pd.noActionTicks]; };
SELECT cDesc.cState.state FROM
active => RETURN;
idle => EXIT;
ENDCASE;
ENDLOOP;
Complain[info, cDesc, error, "Finch failed to connect to voice service."];
};

JayConnection: INTERNAL PROC[newConn: BOOL_TRUE] RETURNS [
jayOpen: BOOL_FALSE,
cDesc: ConvDesc_NIL,
state: StateInConv_idle
] = {
calledPartyID: PartyHandle;
IF NOT (([,cDesc, state]_FinchOn[]).on) THEN {
jayOpen_RepRet[FALSE, noSuchParty, "Your Finch is not running"]; RETURN; };
SELECT state FROM
idle, reserved => IF newConn THEN {
calledPartyID _ ThParty.GetParty[shh: info.shh, partyID: info.partyID, rName: "Recording", type: service];
IF calledPartyID # Thrush.nullHandle THEN
cDesc _ Connect[calledPartyID, TRUE, FALSE, normal, TRUE];
};
ENDCASE;
jayOpen_RepRet[IF cDesc=NIL THEN FALSE ELSE cDesc.bluejayConnection, noSuchConv, "Connection to voice server failed"];
};

ProseConnection: INTERNAL PROC[newConn: BOOL_TRUE] RETURNS [
proseOpen: BOOL_FALSE,
cDesc: ConvDesc_NIL,
state: StateInConv_idle
] = {
calledPartyID: PartyHandle;
IF NOT (([,cDesc, state]_FinchOn[]).on) THEN {
proseOpen_RepRet[FALSE, noSuchParty, "Your Finch is not running"]; RETURN; };
SELECT state FROM
idle, reserved => IF newConn THEN {
calledPartyID _ ThParty.GetParty[shh: info.shh, partyID: info.partyID, rName: "Text-to-Speech", type: service];
IF calledPartyID # Thrush.nullHandle THEN
cDesc _ Connect[calledPartyID, FALSE, TRUE, normal, TRUE];
};
ENDCASE;
proseOpen_RepRet[IF cDesc=NIL THEN FALSE ELSE cDesc.proseConnection, noSuchConv, "Connection to text-to-speech server failed"];
};

RepRet: PROC[bool: BOOL, nb: NB, remark: Rope.ROPE]
RETURNS[sameBool: BOOL] = {
IF bool=FALSE THEN
IF info#NIL THEN info.ReportConversationState[nb, NIL, remark]
ELSE VoiceUtils.Report[remark, $Finch];
sameBool_bool;
};

Problem: PROC[remark: ROPE_NIL] = { VoiceUtils.Problem[remark, $Finch]; };

Feep: PUBLIC ENTRY PROC[feepString: ROPE] = {
cDesc: ConvDesc;
IF info=NIL OR info.conversations=NIL OR info.currentConvID=nullConvHandle
THEN RETURN;
cDesc _ GetConv[info.currentConvID, FALSE];
EnqueueProses[cDesc,
LIST[NEW[Thrush.ProseSpecBody_[prose: feepString, direction: play]]]];
};

Transition: TYPE = {
noop, elim, idle, alrt, actv, spvs, invl, ntiy
};

transForStates: ARRAY StateInConv OF ARRAY StateInConv OF Transition _ [
[ elim, invl, invl,    invl, invl, invl, invl, invl,  elim, invl,   elim ], -- idle	 (current)
[ idle, noop, invl,    invl, invl, invl, invl, invl,   alrt,  ntiy,    noop ], -- reserved
[ idle, invl, invl,    invl, invl, invl, invl, invl,   invl, ntiy,   noop ], -- parsing
[ idle, invl, invl,    invl, invl, invl, invl, invl,   noop, ntiy,   noop ], -- initiating

[ idle, invl, invl,    invl, invl, invl, invl, invl,   actv, ntiy,    noop ], -- pending
[ idle, invl, invl,    invl, invl, invl, invl, invl,   noop, ntiy,   noop ], -- maybe
[ idle, invl, invl,    invl, invl, invl, invl, invl,   actv, ntiy,    noop ], -- ringing
[ idle, invl, invl,    invl, invl, invl, invl, invl,   ntiy, ntiy,    ntiy ], -- canActivate

[ idle, invl, invl,    invl, invl, invl, invl, invl,   spvs, ntiy,   spvs ], -- active
[ idle, invl, invl,    invl, invl, invl, invl, invl,   ntiy, invl,   ntiy ], -- inactive
[ elim, alrt, invl,   invl, invl, invl, invl, invl,   alrt, ntiy,     invl ] -- any (nonex)
];

ViewCmd: Commander.CommandProc = TRUSTED {
Nice.View[pd, "Finch PD"];
};
Commander.Register["VuFinch", ViewCmd, "Program Management variables Finch"];
FinchSmarts.Register[NEW[FinchSmarts.ProcsRecord _ [
playbackTune: PlaybackTune,
recordTune: RecordTune,
stopTune: StopTune,
textToSpeech: TextToSpeech,
registerTranslateProc: RegisterTranslateProc,
stopSpeech: StopSpeech,
finchIsRunning: FinchIsRunning
]]];
}.


���&V��FinchSmartsImpl.mesa
Copyright c 1984, 1986 by Xerox Corporation.  All rights reserved.
Last Edited by: Swinehart, May 19, 1986 10:20:34 am PDT
Polle Zellweger (PTZ) July 18, 1986 6:14:30 pm PDT
Declarations
Reset cmd should be in Synthesizer, refer to from here and from LarkOutImpl.
Would prefer BOOLEAN filter field to control whether resets can be sent, this hack encodes it in direction=record. August 20, 1985
Supervision

Update local state information

Fields always extracted
<<Need to check for increasing stateID here, and reject old ones?  If so, enable
test in alrt case below.>>
Extracted if present

Extracted if the event changes our state. 
Extracted if non-standard?

Specific fatal error condition, if any => GOTO Failing;
When you know what ones occur, catch them, and emulate...
ANY => { problem _ "Unknown Finch Smarts Supervisor Failure"; GOTO Failing; };

Record whether or not this is now "our" conversation
State and substate (below) and desired state indicate there's something to do. Do it:
Issue any new requests.
Issue any new requests.  Send multiple proseSpecs as long as they aren't too long.  When that happens, partition cDesc.pendingProses temporarily while calling SetProse.  Can get short, long, short, long misbehavior here, but need semantics of separate requests?
Using SetProse to request "feeps" over trunk connection; no feedback.
Analyze any results of trying to reach a different state.

<< How to disarm the cDesc, which will continue to generate noise?>>
Complain and transition to idle
Set up switching and tones to match state.
After reporting state of conversation (changeNoted set), there is no further use for finished record or playback intervals; delete the leading ones (should be all of the finished ones!)
Client Functions

GetHistory: PUBLIC PROC[ convID: Thrush.ConversationHandle, toState: INT_0 -- i.e., all-- ]
RETURNS [ s: Thrush.EventSequence ] = {
s_ThParty.GetHistory[shhh: info.shh, convID: convID, firstState: 1, lastState: toState];
};

IF convID#info.currentConvID THEN {
info.ReportConversationState[noSuchConv, NIL, "Can't answer that call"]; RETURN; };
Get fone for dest
inst: ThMessageDB.MessageInstance = ThMessageDB.GetMessage["Beep.Lark", 1];
Out of luck, for a while . . . no way to talk about it here!!!!
IF inst#NIL THEN PlBaMe[tune, key: extract from equiv. of inst.];
<<If useTune#newTune, probably won't work -- no key.  Nuthatch will solve.>>
<<<Won't work (key troubles) if new tunes are supplied. Vestigial>>>

That's all, folks . . . for now.

Wait for recording to (fail to) begin.
Recording didn't start or can't be decrypted; return with error value.

Wait for recording or conversation to end.
If state is idle, possibly the interval doesn't know its actual duration.
<< ??? No word ??? >>
Describe... may return a list in error; we only want the outer interval.

Modelled after RecordTune, but it breaks text up into manageable chunks so as to allow speech to start sooner and flush quicker...
dectalkEndSpec is a hack to make the connection last until the DECtalk quits speaking PolleZ, February 12, 1986
For now, assume that everything will work okay from here.
Registration
For the purpose of importing NamesGV, use prior binding of serverInstance if there is one and the server name is the same as before.
Will shortly update our knowledge of what's already going on!!
<<Must eliminate participation in any conversation that only we know enough about to get rid of, and eliminate any evidence of our partipation in any others.  For now, do only the latter thing>>
Utilities
New conversation
Not at present protected by monitor -- FinchToolImpl back-pointer problem.
Not at present protected by monitor -- FinchToolImpl back-pointer problem.
n^2 match (worst-case) of reported interval information matched against the requests that we have made.  This gives us needed progress information.
cDesc.requestedIntervals records all those intervals that have been requested but not denoted finished.  They must finish in order.  If an embedded entry in this list finishes, then the finish notifications for any preceding entries have been lost; here we simulate them.  <<Consider various abnormal finish codes augmenting finish>>
n^2 match (worst-case) of reported prose information matched against the requests that we have made.  This gives us needed progress information.
Avoids duplicate request reports during debugging (caused by a process race)
cDesc.requestedProses records all those intervals that have been requested but not denoted finished.  They must finish in order.  If an embedded entry in this list finishes, then the finish notifications for any preceding entries have been lost; here we simulate them.  <<Consider various abnormal finish codes augmenting finish>>
NOTE: ALL ProseSpecs should be reported explicitly (except ones that were flushed)!!!
rS.queueIt should be FALSE; all of these requests have actually been flushed.
Splice int to the end of cDesc.requestedIntervals, which is guaranteed to be a superset of pendingIntervals.  When pendingIntervals is a trivial subset (NIL), it needs special attention.
reqID unique within 2^16, forget about stateID
Splice prose to the end of cDesc.requestedProses, which is guaranteed to be a superset of pendingProses.  When pendingProses is a trivial subset (NIL), it needs special attention.
reqID unique within 2^16, forget about stateID
cDesc.pendingProses is closer to the end of the list than cDesc.requestedProses is...
Yeah, but maybe it's a different list.
Would really like to be able to distinguish between service dead and service busy for client reports (return param from TextToSpeech).  Also true for JayConnection above.

State Transition Tables
Just codes to dispatch on in Supervisor; explained there
  idle  resrv  pars    init pend mayb ring canAc   activ inact   any -- desired

NB: examine relationship to validity table in PartyOpsImpl someday.
Debugging nonsense

Registration for use by arms-length systems
Swinehart, May 22, 1985 1:08:51 pm PDT
Changes to GetParty.
changes to: JayConnection
Polle Zellweger (PTZ) July 13, 1985 5:20:26 pm PDT
adding Text-to-Speech server
changes to: DIRECTORY, ProseSpec, ProseSpecs, stopIntervalSpec (was stopSpec), stopProseSpec, Progress, Supervise, DisconnectCall, PlaceCall, StopSpeech, TextToSpeech, InitFinchSmarts, GetConv, ReportProses, EnqueueProses, Complain, Connect, ProseConnection
Swinehart, August 6, 1985 5:43:08 pm PDT
Merge PTZ prose changes
changes to: DIRECTORY, NB, PD, stopIntervalSpec, stopProseSpec, Report, Progress, Supervise, DisconnectCall, PlaceCall, StopTune, NoiseSpec, PlaybackTune, TextToSpeech, InitFinchSmarts, GetConv, ReportProses, CompareIntID, EnqueueProses, Complain, Connect, JayConnection, ProseConnection, RepRet, FinchSmarts
Polle Zellweger (PTZ) August 19, 1985 4:16:40 pm PDT
Meter text in TextToSpeech so as to avoid sending large ropes all at once.  Allows speech to begin sooner and flush faster. Also flushing changes.
changes to: FinchInfo, PD, Supervise, TextToSpeech, StopSpeech, ReportProses (comments only)
Polle Zellweger (PTZ) September 3, 1985 6:28:29 pm PDT
Allow registration of defaultTranslateProc.
changes to: Supervise, defaultTranslateProc, RegisterTranslateProc, TextToSpeech, FinchSmarts
Swinehart, September 16, 1985 10:00:59 am PDT
If Finch has never been initialized, info is NIL -- don't let that bother you.
changes to: GetRname, PlayNoise, FinchOn

Polle Zellweger (PTZ) October 22, 1985 5:10:44 pm PDT
changes to: Progress (add prose debugging reports), TextToSpeech (report connection failure), ReportProses (fix debugging reports), JayConnection (report connection failure), ProseConnection (report connection failure)
Polle Zellweger (PTZ) October 24, 1985 4:53:21 pm PDT
Move bluejayConnection and proseConnection from FinchInfo to ConvDesc.
changes to: Supervise, DisconnectCall, InitFinchSmarts, Connect, JayConnection, ProseConnection
Swinehart, October 28, 1985 12:31:20 pm PST
Merge Above changes with other other minor changes (RefQ and the like)
changes to: DIRECTORY, FinchSmartsImpl, Progress, Supervise, DisconnectCall, TextToSpeech, InitFinchSmarts, UninitFinchSmarts, IsConv, GetConv, IsConv (local of GetConvDesc), GetConvDesc, ReportProses, FinchOn, Connect, JayConnection, ProseConnection, PlaybackTune, ClearConvs (local of UninitFinchSmarts)

Polle Zellweger (PTZ) December 13, 1985 2:53:06 pm PST
New function for FinchToolImpl to use for managing selections in conversation log.
changes to: GetCurrentConvID
Swinehart, February 2, 1986 11:01:59 pm PST
intID.stateID couldn't be maintained properly.  Change intID.reqID to be a semi-unique value (cycles every 2^16 requests), and look for that only in incoming reports.  They'll have (correct) stateID values in them, too, but we don't use them for anything.  Fixes a problem where some requests were being played multiple times, others not at all, if things were queued.
changes to: Supervise, ReportProses, EnqueueProses, DIRECTORY

Polle Zellweger (PTZ) February 12, 1986 2:42:36 pm PST
changes to: dectalkEndSpec, TextToSpeech
Swinehart, May 19, 1986 9:11:59 am PDT
Cedar 6.1
changes to: DIRECTORY, FinchSmartsImpl, Report, InitFinchSmarts, FinchOn, RepRet, Problem
Polle Zellweger (PTZ) July 2, 1986 7:07:30 pm PDT
changes to: TextToSpeech, FindTextBreak, SpecialAbbrev, PhonemeCmd
Polle Zellweger (PTZ) July 3, 1986 3:27:40 pm PDT
changes to: dectalkEndSpec, Report, TextToSpeech, FindTextBreak, SpecialAbbrev, PD

Polle Zellweger (PTZ) July 14, 1986 5:29:26 pm PDT
changes to: TextToSpeech
Polle Zellweger (PTZ) July 17, 1986 6:38:46 pm PDT
changes to: DIRECTORY
Polle Zellweger (PTZ) July 18, 1986 1:15:04 pm PDT
changes to: FinchSmartsImpl
Polle Zellweger (PTZ) July 18, 1986 6:14:31 pm PDT
changes to: resetProseSpec, dectalkEndSpec

Ê'ñ��˜�Jšœ™šœ
Ïmœ7™BJšœ7™7Icodešœ2™2—J˜�šÏk	˜	Jšœ
žœ&˜5Jšœ
žœ˜*Jšœ˜Jšžœ˜Jšœžœ
žœ˜Jšœžœ˜%Jšœžœ˜!Jšœžœ˜-Jšœ	žœ˜%J˜J˜�Jšœžœ
˜ Jšœžœ/˜<Jšœžœ+˜5Jšœ˜JšžœžœO˜XJšœ
žœžœ˜ Jšœžœ˜ JšœžœÒ˜ßJšœ˜šœžœ˜
Jšœ‰žœ~žœc˜ò—J˜	Jšœ˜J˜8Jšœžœ
˜Jšœžœ„˜”J˜J˜�—šœžœž˜Jšžœžœdžœv˜ýJšžœ˜!Jšžœžœ˜J˜�—™J˜�Jšœ
žœ˜'Jšœ
žœ˜&šœžœ˜5J˜;—Jšœ
žœ˜'Jšœžœ˜(Jšœžœ˜)Jšœžœ˜+Jšœžœ˜#Jšœžœ˜%Jšžœžœ
žœ˜Jšœžœ˜J˜0Jšœ
žœ˜'Jšœžœ˜Jšžœžœ
žœ˜Jšžœžœžœ˜Jšœžœ˜)Jšœ
žœ˜'J˜�šžœžœžœ˜Jšœžœžœ˜Jšœžœžœ˜Jšœžœ˜Jšœ:˜:Jšœžœ˜Jšœ6˜6Jšœžœžœ˜"Jšœžœžœ˜%Jšœžœžœ˜ Jšœžœ˜Jšœ	žœžœ˜Jšœ	žœž˜JšœžœÏc=˜XJšœ	žœ
˜J˜—J˜�Jšœ˜Jš	œžœžœžœžœ˜J˜�šœ(žœ˜EJšœ1žœ˜:—J˜�šœ"žœ˜<Jšœ%žœ˜.J˜�—šœ#žœ˜=šœZžœ˜cJ™LJšœÏbœg™‚—J˜�—šœ#žœ˜=Jšœ4žœŸ˜OJ˜�—šÏnœžœžœ˜Jšžœžœžœžœ˜ J˜ J˜—J˜�š¡œžœžœžœ˜ Jšžœžœžœžœ˜Jšœžœ˜J˜J˜�——™J™�š¡œžœžœžœ˜Jšœžœ˜
J˜Jšœ˜Jšœžœ˜Jšœ
žœ˜Jšœž˜Jšœžœ˜'Jšžœžœžœ˜Jšœ˜Jšžœžœžœžœ˜Jšœ˜J™J˜�šžœžœ˜šœ˜šžœ*˜,J˜CJšœžœA˜K—šžœ%˜'Jšœ,žœžœžœ˜j———J˜�Jšœ*žœ˜1Jš	žœ?žœžœžœŸ˜`J™�J™J˜-˜=J™PJ™—J˜�J™šžœžœžœ˜Jšœ6žœ˜>—Jšžœžœžœ˜>Jšžœžœžœ˜8Jšžœžœžœ8žœ˜YJ™�J™*šžœžœ˜J˜�š¡œžœ˜
Jšœžœ˜	Jšžœžœžœžœ˜?˜-JšœJ˜J—Jšžœžœžœ˜)J˜—J˜�Jšœžœ˜Jšœ=˜=Jšœ!˜!Jšœ%˜%Jšœ#˜#Jšžœžœžœ1žœ˜OJ™Jšžœžœžœ&˜?Jšžœžœ&˜BJšžœžœ*˜Jšžœ
ž˜J˜+J˜2J˜1J˜9Jšžœ˜—J˜—J˜�J˜J˜J™�Jšœžœ˜Jšžœ
žœŸ,˜OJ˜J˜�—š¡	œžœžœ˜2Jšœ	žœžœ˜Jšžœ;˜Bšžœžœž˜šžœ˜Jšžœžœ˜Jšœ*žœ	™7Jšœ
žœ7˜LJ™9Jšžœ;žœ™NJ˜—Jšœžœ	˜J˜Jšœžœ˜šžœDžœžœž˜aJšœžœ˜.Jšœ+˜+Jšœ
žœ˜Jšœžœ:˜DJšœžœŸ8˜NJ˜�šžœ
žœžœ˜#šžœžœ˜šœ˜šžœ&˜(J˜QJšœžœ žœ#˜d—šžœ˜Jšœžœ;˜EJšœžœžœžœ˜(———J˜J˜—J™�Jšžœžœžœžœ˜!J™4šžœ
ž˜Jšœžœžœ%˜9˜QJ˜
Jšžœžœ ˜BJšœ5˜5J˜—Jšœ)˜)Jšœžœ˜Jšžœžœ˜—J™Ušžœ6ž˜@Jšœžœ˜
šœ	˜	Jšœ0žœ˜4Jšœ2ž˜8Jšœ*žœ˜.J˜—šœ	Ÿ+˜4J˜Jšžœžœžœ"˜2Jšžœžœžœ˜>šœ˜J˜&Jšœ$˜$Jšœžœžœ
žœ˜DJ˜Jšœ˜Jšœ˜—šžœžœ˜J˜>Jšœžœ˜
J˜—J˜—šœŸ˜#šœ˜J˜J˜&Jšœ˜J˜Jšœ˜Jšœ˜——šœ	˜	šžœžœžœ˜$JšŸ™šœ˜J˜J˜&Jšœ%˜%Jšœ˜—Jšžœžœžœ˜.Jšœ˜—šžœžœžœ˜!Jšœ…™…Jšœžœ˜#Jšœ;˜;Jšœžœ˜Jšœ	žœ˜šžœ1žœžœž˜DšžœB˜DJšžœ˜—šžœ˜Jšœ˜Jšœžœ˜Jšž˜J˜—Jšžœ˜—šœ˜J˜J˜&Jšœ˜Jšœ˜—JšœŸN˜gšžœžœ˜Jšœ˜šžœžœžœ˜;J™E—J˜—Jšœ˜—J˜—˜	J˜:Jšœ
žœ˜J˜J˜J˜2J˜—˜	J˜>Jšœ
žœ˜J˜J˜J˜8J˜—Jšžœ
˜—J™9J˜�šžœžœž˜#Jšœžœ'žœžœ˜E—J™�šžœž˜Jšœžœ˜šœŸ2˜BJšœ:˜:—šœŸ2˜@JšœZ˜Z—šœ˜Jšœn˜nJ™DJ˜—šœ6˜6Jšœ™Jšœ	žœ9˜FJ˜Jšœ&˜&Jšœ˜—šœŸ%˜@Jšœ	žœ˜(Jšœ˜Jšžœžœ%˜1Jšœ1˜1J˜%Jšœ&˜&Jšœ˜—šœŸ/˜NJšœF˜FJšžœ	˜
J˜—Jšžœ
˜—J™*Jšžœ
žœ.žœ˜CJ™¹šžœ9žœžœž˜Lšžœžœž˜9Jšœ#˜#—Jšžœžœ˜
Jšžœ˜—šžœ3žœžœž˜Fšžœžœž˜9Jšœ ˜ —Jšžœžœ˜
Jšžœ˜—šžœžœ˜JšœE˜EJšœžœ˜Jšœ˜—Jšžœ˜—Jšžœžœžœžœ˜&Jšžœžœžœžœ˜,Jšžœžœžœžœ˜&Jšžœ(Ÿ
˜;Jšžœ˜—Jšœžœ˜J˜J˜�——™J™�š¡
œžœ.žœŸœ™[Jšžœ ™'J™XJ™J™�—š
¡œžœžœžœ	žœ˜LJšžœžœžœžœžœžœ9˜YJ˜J˜�—š¡œžœžœžœ˜"Jšœ#Ÿ˜2J˜"Jšœ	žœžœ˜Jšžœžœžœ˜J˜$Jšžœžœ!žœžœ˜3Jšœ2žœ˜8šžœž˜šœ˜Jšœ,žœ#˜RJšžœ˜J˜—Jšœžœžœ˜=Jšžœ˜—J˜,Jšœ˜J˜�—š
¡
œžœžœžœ#Ÿœ˜XJšžœžœžœ˜J˜$Jšžœžœ!žœžœ˜3šžœž˜šœžœ˜šžœžœ™#Jšœ)žœžœ™S——Jšžœžœ˜—Jšœ˜Jšœ˜J˜�—š¡	œžœžœžœ˜Jšœ#Ÿ˜5JšœžœŸ˜$JšœžœŸ˜-Jšœ#˜#Jšœžœžœ˜Jš
žœžœžœžœ=žœ˜fJšœ™J˜Jšœžœ˜Jšžœžœžœžœ˜"šœžœžœž˜ šœž˜šœe˜eJšœ˜——šœžœ˜
Jšœsžœ˜y—Jšœžœžœ˜%šœZžœ˜`šœ˜Jšœ:˜:Jšœ!žœ˜'——Jšžœ˜—šžœžœ˜$šœ+žœ˜/Jšžœžœžœ(˜9Jšžœ8˜<—J˜—Jšœžœžœ˜1Jšœ˜J˜�—š¡
œžœžœžœ˜J˜J˜"Jšœ	žœž˜Jšœ˜Jšžœ˜Jšœ*˜*J˜"J˜"J˜(J˜Jšžœžœžœ˜J™KJ™?J™AJ™LJ™DJ™�Jšœ˜J˜$Jšœ	žœžœ˜š
žœžœ žœžœžœ˜BJ™ —šœ
žœ˜)Jšœ3˜3Jšœ2˜2Jšœ˜—J™�J™&Jšœžœ˜'J˜-Jšœ˜J˜�šžœ
žœžœžœ˜/J™FJšžœžœ@˜RJšžœ ˜&J˜—J™�J™*šžœžœž˜:Jšžœ˜Jšžœ˜—JšžœN˜TJ™IJšœ˜—š¡œžœžœ,˜MJšžœ
žœžœ˜ Jšžœžœžœ˜Jšžœ8˜?šžœžœžœž˜(JšžœŸ4˜HJšžœžœžœžœ˜FJšžœ˜—Jšžœ;˜BJ˜J˜�—š¡œžœžœžœ*˜EJšžœžœžœ˜J˜JšžœžœžœžœžœŸ˜VJšœžœžœ.˜NJšœ˜—š¡
œžœžœžœ*˜GJšžœžœžœ˜J˜Jšžœžœžœ
žœžœŸ˜ZKšœ˜Jšœžœžœ(˜EJšœ˜—š¡
œžœžœžœ*˜GJšžœžœžœ˜J˜Jšžœžœžœ
žœžœŸ˜ZKšœ˜Jšœžœžœ)˜FJšœ˜—š¡œžœžœžœ˜!Jšœ˜J˜J˜Jšœ	žœžœ˜JšœžœŸD˜RJšœžœž˜Jš
œžœžœžœŸÐckŸ(˜UJšžœžœžœ˜J˜�J˜$Jšœžœ˜Jšœžœ˜
J˜J˜šžœžœ˜Jšœ,žœžœŸ˜T—š
žœžœ žœžœžœ˜BJšœ™—˜J˜T—šžœžœžœ˜)Jšžœ	žœA˜PJšžœ˜J˜—J•StartOfExpansion[]šœžœQ˜[šœ˜šœ˜Jšœ6˜6Jšœ"žœžœŸ&˜T——šžœ	žœ˜Jšžœ	žœ:˜IJšžœ˜J˜—Jšžœžœžœ	žœ˜%J˜šžœ+žœžœž˜=J™Hšžœ
žœ˜'J˜I—Jšžœ˜—J˜]Jšœ ˜ Jšžœžœ+˜7Jšœ˜J˜�—Kšœ5žœ˜9š¡œžœžœ,žœ˜VKšœ!˜!K˜K˜�—š¡œžœžœžœ˜!Kšœžœžœžœ˜%Kšœ3žœ˜8Kšžœ*˜1Kšžœžœžœ˜K™�K™‚Kšœ˜J˜$Kšžœžœžœ ˜>Kšžœžœžœžœ#˜Hšžœžœ"žœž˜>Jšžœ˜—Kšžœ
žœŸ˜Jšžœ#ž˜*Jšœžœžœ˜JšœV˜Všœ
žœ˜&JšœB˜BJšœ˜—Jšœžœ˜$Jšœ
žœ˜Kšžœ˜—šœ
žœ˜&Jšœ=˜=Jšœ˜—šœžœ˜4Jšœo™o—Kšœ9™9K˜—K˜�—™J˜�š¡œžœžœ˜Jšœžœžœ˜ Jš¡œžœžœ˜$Jš¡œžœžœ žœ˜KJšœ˜Jšœ	žœžœ˜Jšžœžœ4žœ˜QJ˜J˜J˜0Jšœžœžœ˜Jšœžœžœ˜!J˜ J˜AJ˜�Jšœ˜J˜�JšœžœŸ˜;Jšœžœ˜Jšœžœ˜J˜$Jšœžœ˜Jšœ)˜)Jšœ5˜5šœ9˜9Jšžœžœžœ˜)JšžœQ˜U—šœ˜J˜J˜u—Jšœ)˜)Jšœ.˜.˜#J˜Jšœ˜Jšœ˜—šœžœ˜J˜�—J™„J˜Všžœžœžœ)žœ˜pJšœ/žœ˜B—J˜�Jšœžœžœžœ˜@šžœ˜!Jšœ˜Jšœ˜Jšœ˜JšœŸœ
˜Jšžœ:žœ˜OJ˜�—šœ
˜
JšœOžœ˜UJ˜�—˜"JšœO˜OšœŸžœ˜(šœ˜šœ=˜=Jšœ˜——Jšžœ˜Jšœ˜——Jšœžœ˜J˜�JšœR˜RJšžœžœ)žœ˜]˜Jšœ,žœ/˜^J˜V—J˜�Jš	žœžœžœ&žœŸ˜~J˜Jšœ˜˜?J™>—Jšœžœ˜Jšœ#˜#šž˜J˜)—J˜—J˜�š
¡œžœžœ
žœžœ˜5J™ÂJšžœžœžœ˜%Jšžœ	žœžœ˜%šžœžœžœ˜šžœžœžœž˜KJšœ+žœ
žœ˜E—J˜Jšœžœ˜šœ˜š¡
œ˜Jšœžœ˜'Jšœžœ˜Jšœ˜—Jšœ,˜,Jšœžœ˜Jšœ˜—J˜—Jšœžœ˜šžœžœž˜AJšœ˜—Jšœžœ˜šžœž˜JšœBžœ˜L—Jšœžœ˜šž˜Jšœ;žœ˜A—˜J˜�——š
¡œžœžœžœžœ˜VJ˜�——™	J˜�š¡œžœžœ)ž˜JJšœžœžœŸ
œ˜0š¡œ˜Jšœžœ˜Jšžœ*žœžœžœ˜>Jšœ˜—Jšžœžœ&žœžœ˜NJšœ™Jšœžœ˜)Jšœ'˜'Jšœ˜J˜"Jšœ"˜"šœ˜J˜L—Jšœ=˜=šžœž˜Jšœžœ_˜h—J˜—J˜�š¡œžœžœžœ˜BJšœžœžœŸ3˜Pšžœžœ˜4Jšžœžœ˜$—˜6Jšœžœžœ˜#—Jš
žœžœžœžœ	žœ˜:Jšžœžœ˜J˜J˜�—š¡œžœžœžœ˜UJ™Jš¡œ˜Jšœžœ˜Jšžœ*žœžœžœ˜>Jšœ˜—Jšžœžœžœžœ˜*šžœžœ&žœ˜BJšžœžœžœ˜—Jšœ˜J˜�—š¡œžœžœ!˜FJ™JJšžœ˜Jšœ˜J˜�—J˜�š¡œžœžœŸ
œ˜=šžœžœž˜Jšžœ#žœ˜C—Jšœžœ˜Jšž	œ˜J˜J˜�—š¡œžœžœ.˜LJ™“šžœ4žœžœž˜GJ˜Jšœžœ˜ šžœ9žœžœž˜LJ˜Jšžœžœžœ˜#J˜J™ÍšžœžœŸ˜-šžœ9žœ	ž˜Lšžœžœ˜#Jšœ1žœ˜:—Jšžœ˜——Jšžœ˜Jšžœ˜—Jšžœ˜—J˜—J˜�š¡œžœžœ.˜IJ™šžœ.žœžœž˜AJšœ˜Jšœžœ˜ š	žœ3žœžœžœž˜bJšœ˜Jšžœžœžœ˜#šžœžœŸ˜6KšœL™L—JšœŸœ¶™ÊJ™UšžœžœŸ˜-šžœ3žœ	ž˜Fšžœžœ˜#J™MJšœ1žœ˜:—Jšžœ˜——Jšžœ˜Jšžœ˜—Jšžœ˜—J˜J˜�—š¡œžœžœ*˜IJšœ™žœ™ºšžœ$žœžœž˜7šœ1˜1Jšœ.™.—Jšžœ˜—Jšžœžœžœ˜>Jšžœžœžœ˜Aš	žœžœ9žœžœž˜QJšžœ
žœžœžœ˜/Jšžœ˜—J˜J˜—J˜�š¡
œžœžœ)˜EJšœ’žœ™³šžœ#žœžœž˜6šœ1˜1Jšœ.™.—Jšžœ˜—Jšžœžœžœ˜:Jšžœžœžœ˜=š	žœžœ3žœžœž˜KJšœU™UJ™&Jšžœ
žœžœžœ˜1Jšžœ˜—J˜J˜J˜�—š¡œžœžœ˜7šžœ3žœžœž˜FJšžœžœžœžœ˜?Jšžœ˜—Kšœžœ˜K˜J˜�—š
¡œžœžœDžœžœ˜hJšœžœžœžœ
˜GJ˜J˜J˜"Jšœžœ˜Jšœ˜JšœŸ8˜GJ˜J˜�—š¡œžœžœžœ˜ Jšœžœžœžœ˜Ašžœ
žœžœžœ˜!Jšœ8žœ˜B—Jšœžœ˜Jšœ(˜(Jš	œžœžœžœžœ˜5J˜J˜�—š¡œžœžœ˜J˜J˜J˜J˜Jšœ	žœž˜J˜J˜Jšœ˜Jšœ˜J˜J˜J˜�—š¡œžœžœ˜Jš	œ/žœžœ.žœžœ˜ƒJšžœ˜Jšœ˜J˜šžœž˜Jšœ*žœ˜KJšœžœ˜šžœ˜Jšœ.žœ&˜WJšžœ˜—Jšœ˜—Jšœ,˜,Jšœ(˜(J˜%Jšœžœ˜Jšœ˜J˜Jšžœžœžœ˜šžœžœžœž˜(Jšžœ8˜?JšžœŸ4˜HJšžœ;˜Bšžœž˜Jšœ
žœ˜Jšœžœ˜
Jšžœ˜—Jšžœ˜—J˜JJšœ˜J˜�—š¡
œžœžœ
žœžœžœ˜:Jšœ	ž˜Jšœžœ˜Jšœ˜Jšœ˜J˜šžœžœ!žœ˜.Jšœžœ-žœ˜K—šžœž˜šœžœ	žœ˜#Jšœj˜jšžœ#ž˜)Jšœžœžœ
žœ˜:—J˜—Jšžœ˜—JšœžœžœžœžœžœK˜vJšœ˜J˜�—š¡œžœžœ
žœžœžœ˜<Jšœž˜Jšœžœ˜Jšœ˜Jšœ˜J˜šžœžœ!žœ˜.Jšœžœ-žœ˜M—šžœž˜šœžœ	žœ˜#Jšœo˜oJšœª™ªšžœ#ž˜)Jšœžœžœ
žœ˜:—J˜—Jšžœ˜—KšœžœžœžœžœžœR˜Jšœ˜J˜�—š
¡œžœžœžœžœ˜3Jšžœžœ˜šžœžœž˜Jšžœžœžœ"žœ	˜>Jšžœ#˜'—J˜J˜J˜�—š¡œžœ	žœ,˜JJ˜�—š¡œžœž
œ
žœ˜-Jšœ˜š
žœžœžœžœžœ"˜JJšžœžœ˜—Jšœ$žœ˜+šœ˜Jšžœžœ>˜F—Jšœ˜J™�——™J˜�˜J™8J˜.J˜—J˜�š	œžœ
žœžœ
žœ˜HJšœO™OJ™�JšœLŸ˜^JšœOŸ˜ZJšœMŸ
˜WJšœMŸ
˜ZJ˜�JšœNŸ
˜XJšœMŸ˜UJšœNŸ
˜XJšœNŸ˜\J˜�JšœMŸ	˜VJšœMŸ˜XJšœMŸ˜[J˜JšÏsC™C——J˜�™šœ!žœ˜*Jšœ˜Jšœ˜—JšœM˜MJ™�—™+šœžœ˜4J˜Jšœ˜Jšœ˜J˜J˜-J˜Jšœ˜J˜——J˜J˜�J˜�™&K™KšœÏr
™—™2K™Kšœ¤2œ¤´™—™(K™Kšœ¤¨™´—™4Kšœ¤œx™’Kšœ¤P™\—šœ¤ ™6Kšœ¤œ™+Kšœ¤Q™]—™-K™NKšœ¤™(—K™�šœ5™5Kšœ¤	œ¤œ¤œ¤œ¤œ™Ú—šœ5™5KšœF™FKšœ¤S™_—™+K™FKšœ¤Šœ¤gœ™±—K™�™6K™RKšœ¤™—™+K™ðKšœ¤1™=—K™�™6Kšœ¤™(—™&K™	Kšœ¤M™Y—™1Kšœ¤6™B—™1Kšœ¤F™R—K™�™2Kšœ¤™—™2Kšœ¤	™—™2Kšœ¤™—™2Kšœ¤™*—K™�—�…—����„B��Ò‰��