DIRECTORY
BluejaySmarts,
GList			USING [ DRemove, Nconc ],
IO,
Jukebox		USING [ Handle, IntervalSpec, VoiceDirection ],
MBQueue     USING [ QueueClientAction ],
Process USING [ SecondsToTicks, SetTimeout ],
PupSocket		USING [ SetGetTimeout, SetRemoteAddress, Socket ],
RecordingServiceRegister USING [ jayShh, jukebox, numParties ],
RefID		USING [ ID ],
ThParty		USING [ Advance, ConversationInfo, GetConversationInfo, GetKeyTable, GetPartyInfo, PartyInfo, RegisterKey, ReportAction ],
ThPartyPrivate USING [ GetPupSocket ],
Thrush		USING [ ActionID, ActionReport, ConversationID, ConvEvent, Credentials, EncryptionKey, NB, NetAddress, notReallyInConv, nullConvID, PartyID, ROPE, SHHH, SmartsID, StateInConv ],
ThSmarts,
TU USING [ RefAddr ],
VoiceStream	USING [ Close, VoiceStreamEvent, Handle, NotifyProc, Open, SetSocket, wholeTune ],
VoiceUtils	USING [ Problem, ProblemFR, ReportFR ]
;

BluejaySmartsImpl: CEDAR MONITOR
IMPORTS GList, IO, MBQueue, Process, PupSocket, RecordingServiceRegister, ThParty, ThPartyPrivate, TU, VoiceStream, VoiceUtils
EXPORTS BluejaySmarts, ThSmarts = {
OPEN IO;


ConversationID: TYPE = Thrush.ConversationID;
nullConvID: ConversationID = Thrush.nullConvID;
PartyID: TYPE = Thrush.PartyID;
SHHH: TYPE = Thrush.SHHH;
SmartsID: TYPE = Thrush.SmartsID;
StateInConv: TYPE = Thrush.StateInConv;
JayInfo: TYPE = BluejaySmarts.JayInfo;

NB: TYPE = Thrush.NB;
IntID: TYPE = BluejaySmarts.IntID;
nullIntID: IntID = BluejaySmarts.nullIntID;
IntervalSpec: TYPE = Jukebox.IntervalSpec;
IntervalReq: TYPE = BluejaySmarts.IntervalReq;

infos: PUBLIC ARRAY[0..100) OF BluejaySmarts.JayInfo_ALL[NIL];
keyDistributionTimeoutInSeconds: INT _ 300;

ConvDesc: TYPE = BluejaySmarts.ConvDesc;
ConvDescBody: TYPE = BluejaySmarts.ConvDescBody;
NconcIntervals: PROC[l1, l2: LIST OF IntervalReq] RETURNS[LIST OF IntervalReq] =
INLINE { RETURN[NARROW[GList.Nconc[l1, l2]]]; };


Progress: PUBLIC ENTRY PROC[
shh: Thrush.SHHH,
convEvent: Thrush.ConvEvent
] = {
ENABLE UNWIND => NULL;
info: JayInfo = InfoForSmarts[smartsID: convEvent.self.smartsID];
convID: Thrush.ConversationID = convEvent.self.convID;
cDesc: ConvDesc _ GetConv[info, convID];
whatNeedsDoing: WhatNeedsDoing;
IF cDesc=NIL THEN { VoiceUtils.Problem["No info at Progress", $Bluejay]; RETURN; };

IF convEvent.self.partyID = convEvent.other.partyID THEN { -- own state changed
NoteNewState[cDesc, convEvent];
SELECT info.currentConvID FROM
convID, nullConvID => NULL;
ENDCASE => []_ChangeState[cDesc, $idle, $busy, "One conversation at a time, please"];
RETURN;
};
IF convID#info.currentConvID THEN { ForgetConv[cDesc]; RETURN; };

whatNeedsDoing _ whatNeedsDoingIf[cDesc.situation.self.state][convEvent.other.state];
SELECT whatNeedsDoing FROM
$noop, $ntiy, $reac, $deac => NULL;
-- No action is needed, or we don't yet know what one to take.
$imp => ERROR; -- This is supposed to be impossible!
$xrep => VoiceUtils.Problem["Didn't expect state change report", $Bluejay];
$frgt => ForgetConv[cDesc];
$invl => {
VoiceUtils.Problem["Invalid state transition", $Bluejay];
[]_ChangeState[cDesc: cDesc, state: $idle,
reason: $error, comment: "System Error: Invalid state transition"];
};
$idle => {
nb: Thrush.NB; cInfo: ThParty.ConversationInfo;
[nb, cInfo] _ ThParty.GetConversationInfo[shh: RecordingServiceRegister.jayShh, convID: convID];
SELECT nb FROM
$success => NULL;
$noSuchConv => {
VoiceUtils.ProblemFR["BluejaySmarts (%g): Conversation disappeared, can't get ConversationInfo", $Bluejay, NIL, TU.RefAddr[cDesc.info]];
ForgetConv[cDesc];
RETURN;
};
ENDCASE => ERROR;
IF (cInfo.numParties-cInfo.numIdle) <= 1 THEN
[]_ChangeState[cDesc, $idle, $terminating];
};
ENDCASE => ERROR;
};

Substitution: PUBLIC ENTRY PROC[
shh: Thrush.SHHH,
convEvent: Thrush.ConvEvent,
oldPartyID: Thrush.PartyID,
newPartyID: Thrush.PartyID
] = {
ENABLE UNWIND => NULL;
info: JayInfo = InfoForSmarts[smartsID: convEvent.self.smartsID];
cDesc: ConvDesc  _ GetConv[info, convEvent.self.convID];
IF cDesc=NIL THEN { VoiceUtils.Problem["No info at Substitution", $Bluejay]; RETURN; };
NoteNewState[cDesc, convEvent];
};

ReportAction: PUBLIC ENTRY PROC[
shh: SHHH,
report: Thrush.ActionReport
] = {
ENABLE UNWIND => NULL;
info: JayInfo = InfoForSmarts[smartsID: report.self.smartsID];
convID: Thrush.ConversationID = report.self.convID;
cDesc: ConvDesc _ GetConv[info, convID];
IF cDesc=NIL THEN { VoiceUtils.Problem["can't find conversation for report", $Bluejay]; RETURN; };
SELECT report.actionClass FROM
$keyDistribution => { 
BROADCAST cDesc.keysMightBeDistributed; 
cDesc.keysDistributed _ TRUE; 
RETURN; 
};
ENDCASE=> shh _ shh; -- a place to stand during debugging
};

NoteNewState: INTERNAL PROC[cDesc: ConvDesc, convEvent: Thrush.ConvEvent] = {
OPEN now: cDesc.situation.self;
nb: Thrush.NB;
state: StateInConv _ convEvent.self.state;
previousState: StateInConv = cDesc.situation.self.state;
info: JayInfo = cDesc.info;
cDesc.situation _ convEvent^;
IF state = previousState THEN RETURN; -- No conceivable value in acting.
IF info.currentConvID=nullConvID THEN info.currentConvID _ cDesc.situation.self.convID;
SELECT state FROM
$notified => {
nb _ OpenConnection[cDesc]; -- Set up Bluejay streams, socket stuff
IF nb=$success THEN [] _ ChangeState[cDesc, $active]; -- Errors have been dealt with
};
$idle, $neverWas => ForgetConv[cDesc];
$active => NULL; -- Need take no action until recording or playback requested.
ENDCASE;
};

GetConversation: PUBLIC ENTRY PROC [  -- exported to BluejaySmarts
smartsID: Thrush.SmartsID,
conv: Thrush.ConversationID
]
RETURNS [nb: Thrush.NB_$success, cDesc: ConvDesc] = {
ENABLE UNWIND => NULL;
info: JayInfo _ InfoForSmarts[smartsID];
cDesc _ GetConv[info, conv];
nb _ SELECT TRUE FROM
info=NIL => $noSuchSmarts2,
conv=nullConvID OR cDesc=NIL => $noSuchConv,
conv#info.currentConvID => $notInConv,
cDesc.situation.self.state#$active => $convNotActive,
ENDCASE => $success;
IF nb=$success AND cDesc.keyTable=NIL THEN
[, cDesc.keyTable] _ ThParty.GetKeyTable[info.shh, cDesc.situation.self];
};

DistributeKey: PUBLIC ENTRY PROC [  -- exported to BluejaySmarts
cDesc: ConvDesc,
key: Thrush.EncryptionKey,
wait: BOOL_FALSE
]
RETURNS [nb: Thrush.NB, keyIndex: [0..17B]] = TRUSTED {
ENABLE UNWIND => NULL;
keyID: LONG POINTER TO Thrush.ActionID = LOOPHOLE[LONG[@key]];
num: NAT;
[nb, keyIndex] _ ThParty.RegisterKey[credentials: cDesc.situation.self, key: key];
SELECT nb FROM
$success, $newKeys => NULL;
$noSuchSmarts, $noSuchParty, $noSuchConv, $notInConv, $interfaceError => {
VoiceUtils.Problem["Serious problem in DistributeKey"]; RETURN; };
ENDCASE => ERROR;
IF wait THEN {
[nb, num] _ ThParty.ReportAction[report: [other: cDesc.situation.self, requestingParty: cDesc.situation.self.partyID, actionID: keyID^, actionClass: $keyDistribution, actionType: $newKeys], reportToAll: TRUE, selfOnCompletion: TRUE];
SELECT nb FROM
$success => NULL;
$noSuchSmarts, $noSuchParty, $noSuchConv, $notInConv, $interfaceError => {
VoiceUtils.Problem["Serious problem in DistributeKey"]; RETURN; };
ENDCASE => ERROR;
IF num=0 THEN RETURN;
nb _ $newKeys;
cDesc.keysDistributed _ FALSE;
Process.SetTimeout[@cDesc.keysMightBeDistributed, Process.SecondsToTicks[keyDistributionTimeoutInSeconds]]; 
WAIT cDesc.keysMightBeDistributed;
IF ~cDesc.keysDistributed THEN {
[] _ ChangeState[cDesc, $idle, $error, "Could not distribute encryption key"];
nb _ $keyReportTimedOut;
};
};
};


SetInterval: PUBLIC ENTRY SAFE PROC [ir: IntervalReq]  -- exported to BluejaySmarts
RETURNS [nb: Thrush.NB_$success] = CHECKED {
ENABLE UNWIND => NULL;
IF ir.iSpec.tuneID <0 THEN RETURN[nb: $noTuneSpecified];
IF ir.iSpec.length = -1 THEN ir.iSpec.length _ VoiceStream.wholeTune;
IF ir.intID # nullIntID THEN {
ir.reportRequested _ TRUE;
IssueReport[ir, $scheduled];
};
ir.cDesc.info.intervalReqs _ NconcIntervals[ir.cDesc.info.intervalReqs, LIST[ir]];
};

IssueReport: INTERNAL PROC[req: IntervalReq, event: VoiceStream.VoiceStreamEvent] = {
cDesc: ConvDesc _ req.cDesc;
info: JayInfo _ cDesc.info;
nb: NB;
SELECT event FROM
$started, $scheduled => IF ~req.firstInterval THEN RETURN;
$finished, $flushed => IF ~req.lastInterval THEN RETURN;
ENDCASE;
IF cDesc.situation.self.state <= Thrush.notReallyInConv OR NOT req.reportRequested THEN RETURN;
nb _ ThParty.ReportAction[
shhh: RecordingServiceRegister.jayShh,
report: [
self: cDesc.situation.self, -- placeholder, will be filled in by ThParty
other: cDesc.situation.self, 
requestingParty: req.requestingParty,
actionID: req.intID,
actionClass: IF req.direction = $record THEN $recording ELSE $playback,
actionType: event
],
reportToAll: TRUE
].nb;
IF nb#$success THEN VoiceUtils.Problem["Bluejay report failed", $Bluejay];
};

IREvent: TYPE = REF IREventRec;
IREventRec: TYPE = RECORD [
ir: IntervalReq,
event: VoiceStream.VoiceStreamEvent
];

ReportFromBluejay: VoiceStream.NotifyProc = TRUSTED {
ir: IntervalReq _ NARROW[clientData];
irE: IREvent;
IF ir=NIL OR ir.cDesc=NIL THEN RETURN; -- We don't report actions that do not affect our requests
irE _ NEW[IREventRec _ [ir, event]];
ir.cDesc.info.notifications.QueueClientAction[QdReportFromBluejay, irE];
};

QdReportFromBluejay: ENTRY PROC[r: REF] = {
irE: IREvent _ NARROW[r];
ir: IntervalReq _ irE.ir;
event: VoiceStream.VoiceStreamEvent _ irE.event;
cDesc: ConvDesc _ ir.cDesc;
info: JayInfo _ cDesc.info;
IF info.intervalReqs=NIL THEN 
VoiceUtils.Problem["Unexpected report from Bluejay", $Bluejay];
SELECT event FROM
$flushed => {
FOR irS: LIST OF IntervalReq _ info.intervalReqs, irS.rest WHILE irS#NIL DO
IF NOT (irS.first.state=$started AND irS.first.direction=record) THEN
irS.first.state _ $flushed;
IF ir=irS.first THEN EXIT;
ENDLOOP;
};
$started, $finished => {
ir1: IntervalReq _ NIL;
FOR irS: LIST OF IntervalReq _ info.intervalReqs, irS.rest WHILE irS#NIL DO
ir1 _ irS.first;
IF ir=ir1 THEN EXIT;
IssueReport[ir1, $flushed];
info.intervalReqs _ irS.rest;
ENDLOOP;
IF ir=ir1 THEN {
IF event=$finished THEN {
info.intervalReqs _ info.intervalReqs.rest; -- Shorten list
IF ir1.state=$flushed THEN event _ $flushed;
};
IssueReport[ir, event];
IF event=$started AND ir1.state # $flushed THEN
ir1.state _ $started;
};
};
ENDCASE => VoiceUtils.Problem["Unexpected report from Bluejay", $Bluejay];
};

GetConv: --PUBLIC-- INTERNAL PROC[info: JayInfo, convID: ConversationID _ nullConvID]
RETURNS [ cDesc: ConvDesc ] = {
IF info = NIL THEN RETURN[NIL];
IF convID = nullConvID THEN convID _ info.currentConvID;
IF convID = nullConvID THEN RETURN[NIL];
FOR convs: LIST OF BluejaySmarts.ConvDesc _ info.conversations, convs.rest WHILE convs#NIL DO
IF convs.first.situation.self.convID = convID THEN RETURN[convs.first];
ENDLOOP;
cDesc _ NEW[ConvDescBody_[]];
cDesc.situation.self.convID _ convID;
cDesc.info _ info;
info.conversations _ CONS[cDesc, info.conversations];
};

InfoForSmarts: INTERNAL PROC [ smartsID: SmartsID ] RETURNS [ info: JayInfo_NIL ] = {
FOR i: NAT IN [0..RecordingServiceRegister.numParties) DO
IF smartsID=infos[i].credentials.smartsID THEN RETURN [ infos[i] ];
ENDLOOP;
};

ChangeState: INTERNAL PROC[
cDesc: ConvDesc, state: StateInConv, reason: ATOM_NIL, comment: ROPE_NIL, secondTry: BOOL_FALSE]
RETURNS [nb: NB_$success] = {
convEvent: Thrush.ConvEvent;
IF cDesc.situation.self.state = state THEN RETURN;
[nb, convEvent] _ ThParty.Advance[
shhh: RecordingServiceRegister.jayShh,
credentials: cDesc.situation.self,
state: state,
reason: reason,
comment: comment,
reportToAll: TRUE -- parameterize if other states than $idle and $active become possible
];
SELECT nb FROM
$success => NoteNewState[cDesc, convEvent];
$convIdle, $bilateralConv, $conferenceConv, $voiceTerminalUnavailable,
$stateMismatch, $interfaceError => {
IF secondTry THEN ERROR; -- Don't loop forever
NoteNewState[cDesc, convEvent];
IF cDesc.situation.self.state#$idle THEN
[]_ChangeState[cDesc, $idle, $error,
"Connection failed due to voice terminal restrictions or system error", TRUE];
};
$noSuchSmarts, $noSuchParty, $noSuchConv, $notInConv =>
VoiceUtils.Problem["Serious problem at Advance", $Bluejay];
ENDCASE =>ERROR;
};
ForgetConv: INTERNAL PROC[cDesc: ConvDesc ] = {
info: JayInfo _ cDesc.info;
CloseConnection[cDesc];
IF cDesc.situation.self.convID = info.currentConvID THEN info.currentConvID _ nullConvID;
info.conversations _ NARROW[GList.DRemove[cDesc, info.conversations]];
};

OpenConnection: INTERNAL PROC[cDesc: ConvDesc] RETURNS[nb: NB] = TRUSTED {
info: JayInfo = cDesc.info;
pInfo: ThParty.PartyInfo;
socket: PupSocket.Socket;
remoteAddress: Thrush.NetAddress;
IF info.stream=NIL THEN info.stream _ VoiceStream.Open[jukebox: RecordingServiceRegister.jukebox, proc: ReportFromBluejay];
[nb, pInfo] _
ThParty.GetPartyInfo[credentials: cDesc.situation.self, nameReq: $none, allParties: TRUE];
IF nb # $success OR pInfo[0].partyID=0 THEN {
VoiceUtils.Problem["No conversation info, or incomplete", $Bluejay]; RETURN; }; -- This is really bad!
socket _ ThPartyPrivate.GetPupSocket[pInfo[1].partyID];
IF socket=NIL THEN ERROR;
remoteAddress _ pInfo[1].socket; -- Transmit to remote net and host
remoteAddress.socket _ pInfo[0].socket.socket; -- Transmit to own assigned socket ID
PupSocket.SetRemoteAddress[socket, remoteAddress];
PupSocket.SetGetTimeout[socket, 100];
VoiceStream.SetSocket[socket: socket, handle: info.stream];
VoiceUtils.ReportFR["C %d ", $Bluejay, NIL, card[info.credentials.smartsID]];
};

CloseConnection: INTERNAL PROC[cDesc: ConvDesc] = TRUSTED {
info: JayInfo = cDesc.info;
IF info.stream#NIL THEN VoiceStream.Close[info.stream];
info.stream _ NIL;
VoiceUtils.ReportFR["D %d ", $Bluejay, NIL, card[info.credentials.smartsID]];
};



WhatNeedsDoing: TYPE = ATOM; -- {

whatNeedsDoingIf: ARRAY StateInConv OF ARRAY StateInConv OF WhatNeedsDoing _ [
[ $imp, $frgt,  $frgt, $frgt, $frgt,  $frgt, $frgt, $frgt, $frgt, $frgt,   $frgt, $frgt], --neverWas
[ $imp, $noop, $frgt, $noop,  $noop,  $noop, $noop, $noop, $noop, $noop,   $noop, $ntiy ], -- idle
[ $imp, $imp,  $imp, $imp,   $imp,   $imp,  $imp,  $imp,  $imp,  $imp,    $imp,  $imp ], --  failed
[ $imp, $imp,  $imp , $imp,   $imp,   $imp,  $imp,  $imp,  $imp,  $imp,    $imp,  $imp ], -- reserved
[ $imp, $imp,  $imp,  $imp,   $imp,   $imp,  $imp,  $imp,  $imp,  $imp,    $imp,  $imp ], -- parsing
[ $imp, $imp,  $imp,  $imp,   $imp,   $imp,  $imp,  $imp,  $imp , $imp,    $imp,  $imp ], -- initiating
[ $imp, $idle,$idle, $invl,  $invl,  $invl, $xrep, $noop, $noop, $ntiy,   $noop, $ntiy ], -- notified
[ $imp, $imp,  $imp,  $imp,   $imp,   $imp,  $imp,  $imp,  $imp,  $imp,    $imp,  $imp ], -- ringback
[ $imp, $imp,  $imp,  $imp,   $imp,   $imp,  $imp,  $imp,  $imp,  $imp,    $imp,  $imp ], -- ringing
[ $imp, $idle,$idle,$invl,  $invl,  $invl, $xrep, $xrep, $noop, $ntiy,   $noop, $ntiy ], -- canActivate
[ $imp, $idle,$idle,$invl,  $invl,  $invl, $xrep, $xrep, $noop, $ntiy,   $reac, $deac ], -- active
[ $imp, $idle,$idle,$invl,  $invl,  $invl, $xrep, $xrep, $noop, $ntiy,   $ntiy,  $ntiy ] -- inactive (current ^)
];

}.
����BluejaySmartsImpl.mesa
Copyright Ó 1985, 1986, 1987 by Xerox Corporation.  All rights reserved.
Last modified by D. Swinehart, January 31, 1987 2:29:44 pm PST
Doug Terry, December 11, 1986 2:30:34 pm PST

Needing this is a travesty.  See comments about sockets in ThPartyPrivate.
Types, Definitions

Call Supervision
Some party has changed state in a conversation presumably relevant.
(new conversation and we're idle) or (this is the one we like)
We have to reject this, since we're already dealing with another conv.
We are (still) willing to seriously consider only one conversation at a time.
Continued activity in a conversation we've given up on.
Someone else's state changed in a conv. we're interested in; see if it means anything to us!
A poacher has substituted for a poachee, or the other way around.  Update state so that if it's us, we know who we are.
Tunes: control of recording and playback

GetConversation.nb~$success
GetConversation.nb~$noSuchSmarts2
GetConversation.nb~$noSuchConv -- actually, conv not known to this smarts
GetConversation.nb~$notInConv -- actually, this smarts doesn't think so.
GetConversation.nb~$convNotActive -- according to this smarts.
We don't want to schedule new voice until the encryption keys for it have been distributed.  An ActionReport is issued to tell everybody about the keys and then tell us that it's told everybody.  We wait one time around a timeout for a special condition variable (ugh) and then give up.
DistributeKey.nb~$success; -- ~wait only
DistributeKey.nb~$newKeys;
DistributeKey.nb~$keyReportTimedOut; -- wait only
DistributeKey.nb~~$ all other errors are serious, fatal to this smarts but not the system.
SetInterval.nb~$success
SetInterval.nb~$noTuneSpecified
Reports are queued because they can be generated directly by procedures called from entry procedures in this module.  Perhaps the queueing should be done by Bluejay?

For each interval processed by Bluejay, a $started and $finished report gets generated.  Additonally a $flushed report may arrive that indicates that an interval and all previous intervals are being flushed.
This routine to process these reports assumes that some reports from Bluejay may get lost.  Any interval prior to the one being reported was not finished normally.  We treat it as if it were flushed.  Reports concerning $flushed intervals are simply noted; the actual $flushed report is issued when Bluejay reports that this interval has been $finished.  For recording, a $flushed report is ignored as long the recording request was $started (since a flush is the usual way to halt recording).

Mark intervals as flushed
Flush old intervals
Issue current report

Utilities

The transition didn't occur.  These things can happen.  We're postulating that the proper response is always to attempt to reach an idle state, before returning the original error code.  Caller must take any additional cleanup action, but usually none is required.
Should fail, as Lark does, so as to do a ForgetConv, create a new instance, etc.  Haven't worked on this yet. 

Neither this nor Bluejay deals at all properly with multicasting.  Worse yet on recording!  See also ThPartyPrivate discussion about sockets, and discussion of socket assignments in LarkSmartsSupImpl.ComputeConnection.
This is a value that includes our own net/host, but the remote party's assigned socket ID.  
OpenConnection.nb~$success
OpenConnection.nb~$ <other bad errors, all possible but dealt with by return from here.>

State Transition Tables
Just codes to dispatch on in Supervisor; explained there
$noop, $idle, $frgt, $reac, $deac, -- cases explained in code
$invl, -- considered an invalid request
$xrep, -- we got a report we feel we shouldn't have got
$ntiy, -- not implemented yet
$imp --  this situation should not arise even in the face of invalid requests
};
If we're in the state identified by the row, and someone else in the conversation reports a transition onto the state identified by the column, what should we do?

 never   idle  failed resrv   pars    init  notif  rback   ring  canAc    activ  inact -- _ (other)
(Clip this table to view without these comments.)
This situation arises when we've forgotten about the conversation that somebody else is still reporting on.
We don't expect to hear from others while we're deciding whether to play
failed column and possibly idle column is bogus!
Swinehart, May 15, 1985 10:30:42 am PDT
Cedar 6.0
changes to: InitJay
Swinehart, May 22, 1985 12:07:31 pm PDT
recording => service, Jay => Recording
changes to: InitJay
Swinehart, May 17, 1986 3:53:47 pm PDT
Cedar6.1
changes to: DIRECTORY, BluejaySmartsImpl, Report, Supervise, OpenConnection, CloseConnection, ReportDoneEntry, InitJay, ReportBluejay
Doug Terry, July 29, 1986 11:41:35 am PDT
Removed operations for recording and playing voice ropes; their implementations are included in VoiceRopeImpl.
changes to: DIRECTORY, BluejaySmartsImpl, IntID, nullIntID, IntervalSpec, NoteNewState, SetInterval, IssueReport, GetConv, InitJay
Doug Terry, July 30, 1986 12:07:36 pm PDT
Moved JayInit to RecordingServiceRegister.
changes to: DIRECTORY, BluejaySmartsImpl, CloseConnection, ConvDescBody
Doug Terry, August 18, 1986 2:16:07 pm PDT
Tracked change to BluejaySmarts.IntervalReqBody.
changes to: DIRECTORY, IntID, nullIntID, SetInterval, IssueReport
Doug Terry, December 9, 1986 5:02:38 pm PST
Changed meachanisms for handling reports from Bluejay.
changes to: IssueReport, QdReportFromBluejay
Doug Terry, December 11, 1986 2:30:34 pm PST
changes to: QdReportFromBluejay

�ÊU��˜�šœ™IcodešœH™HJšœ>™>K™,—J™�šÏk	˜	J˜Jšœœ˜!Jšœ˜Jšœ	œ*˜8Jšœœ˜(Jšœœ ˜-Jšœœ-˜=Jšœœ!˜?Jšœœœ˜Jšœ	œu˜ƒšœœ˜&JšÏtœJž™L—Jš	œœRœ4œœ˜¹J˜	Jšœœ
˜JšœœM˜^Jšœœ!˜1J˜J˜�—šœ
˜ JšœœRœ˜~Jšœ˜#Jšœœ˜J˜�—™J˜�šœœ˜-Jšœ/˜/—Jšœ	œ˜Jšœœ
œ˜Jšœ
œ˜!J˜'Jšœ	œ˜&J˜�Jšœœ
œ˜Jšœœ˜"Jšœ+˜+Jšœœ˜*Jšœ
œ˜.J˜�Jš	œœ	œœœ˜>Jšœ!œ˜+J˜�Jšœ
œ˜(šœœ˜0J™�—šÏnœœ	œœœœœ˜PJšœœœ˜0—J˜�—™J˜�šŸœœœ˜Jšœœ˜Jšœ˜Jšœ˜Kšœœœ˜J™CJšœA˜AJšœ6˜6Jšœ(˜(J˜Jšœœœ8œ˜SJ˜�šœ2œÏc˜OKšœ˜šœ˜šœœ˜Jšœ>™>—šœN˜UJšœF™FK™M——Kšœ˜K˜—šœœœ˜AJ™7—J˜�Jšœ\™\KšœU˜Ušœ˜šœœ˜#Kš >˜>—Kšœœ %˜4KšœK˜KK˜šœ
˜
Kšœ9˜9šœ*˜*KšœC˜C—Kšœ˜—šœ
˜
Kšœœ"˜/Kšœ`˜`šœ˜Kšœœ˜šœ˜Kšœkœœ˜ˆJšœ˜Jšœ˜J˜—Kšœœ˜—šœ'˜-Kšœ+˜+—K˜—Kšœœ˜—J˜J˜�—šŸœœœ˜ Jšœœ˜Jšœ˜J˜J˜Jšœ˜Kšœœœ˜J™wJšœA˜AJšœ8˜8Jšœœœ<œ˜WJ˜J˜J˜�—šŸœœœ˜ Jšœœ˜
Jšœ˜Jšœ˜Kšœœœ˜Jšœ>˜>Jšœ3˜3Jšœ(˜(KšœœœGœ˜bšœ˜šœ˜Kš	œ˜(Kšœœ˜Kšœ˜Kšœ˜—Kšœ $˜9—J˜J˜�—šŸœœœ2˜MKšœ˜Kšœœ˜K˜*K˜8K˜K˜Kšœœœ "˜HKšœœ2˜Wšœ˜šœ˜Kšœ '˜CKšœ
œ# ˜TK˜—K˜&Kšœœ =˜NKšœ˜—K˜K˜�——Jšœ(™(™�š	Ÿœœœœ ˜BJšœ˜Jšœ˜Jšœ˜Jšœ
œ˜5Jšœœœ˜Jšœ(˜(Jšœ˜šœœœ˜Jšœœ˜Jšœœœœ
˜,Jšœœ˜&Jšœ5˜5Jšœ
˜—šœ
œœ˜*JšœI˜I—J˜Jšœ™Jšœ!™!JšœI™IJšœž+™HJšœ!ž™>J˜�—š	Ÿ
œœœœ ˜@Jšœ˜Jšœ˜Jšœœ˜J˜Jšœ
œœ˜7Jšœœœ˜Jšœœœœœœ˜>Jšœœ˜	JšœR˜Ršœ˜Jšœœ˜˜JJšœ8œ˜B—Jšœœ˜—šœœ˜Jšœž™žKšœËœœ˜éšœ˜Jšœœ˜˜JJšœ8œ˜B—Jšœœ˜—Jšœœœ˜Jšœ˜Jšœœ˜Kšœl˜lJšœ˜"šœœ˜ JšœN˜NJ˜J˜—K˜—J˜Jšœ 
™(Jšœ™Jšœ% ™1JšœZ™ZJ˜�—J˜�šŸœœœœœ ˜SJšœ
œ
œ˜,Jšœœœ˜Jšœœœ˜8Jšœœ)˜Ešœœ˜Jšœœ˜Jšœ˜J˜—JšœHœ˜RJ˜Jšœ™Jšœ™J˜�—šŸœ
œ;˜UJ˜J˜Jšœœ˜šœ˜Jšœœœœ˜:Jšœœœœ˜8Jšœ˜—Jšœ6œœœ˜_šœ˜Jšœž˜&šœž˜	Jšœ ,˜HJ˜J˜%J˜Jšœ
œœœ˜GJ˜Jšœž˜—Jšœ
˜Jšœž˜—Jšœ
œ7˜JJ˜J˜�—Jšœvžœ/ž™§J™�Jšœ	œœ˜šœœœ˜J˜J˜#J˜J˜�—šŸœœ˜5Jšœœ
˜%J˜
Jš
œœœ
œœœ :˜aJšœœ˜$J˜HJšœ˜J˜�—šŸœœœœ˜+J™ÏJ™íJ™�Jšœœ˜Jšœ˜J˜0J˜J˜šœœœ˜Jšœ?˜?—šœ˜šœ
˜
J™šœœœ+œœ˜Kšœœœ˜EJšœ˜—Jšœœœ˜Jšœ˜—Kšœ˜—˜Jšœœ˜J™šœœœ+œœ˜KJ˜Jšœ	œ˜Jšœ˜Jšœ˜Jšœ˜—J™šœœ˜šœœ˜Jšœ, ˜;Jšœœ˜,J˜—Jšœ˜šœœ˜/Kšœ˜—J˜—K˜—KšœC˜J—J˜—˜�J™�——™	J™�š
Ÿœ Ðck œœœ4˜UJšœ˜Jš
œœœœœ˜Jšœœ˜8Jšœœœœ˜(šœœœ9œœ˜]Jšœ,œœ˜GJšœ˜—Jšœœ˜Jšœ%˜%J˜Jšœœ˜5J˜—J˜�š
Ÿ
œœœœœ˜Ušœœœ*˜9Jšœ(œœ˜CJšœ˜—Jšœ˜J˜�—šŸœœœ˜Jš
œ-œœœœ
œœ˜`Jšœœ˜J˜Jšœ$œœ˜2šœ"˜"Jšœ&˜&J˜"Jšœ
˜
Jšœ˜Jšœ˜Jšœ
œ F˜XJ˜—šœ˜K˜+KšœF˜Fšœ$˜$Kšœˆ™ˆKšœœœ ˜.K˜šœ"˜(šœ$˜$KšœHœ˜N——K˜—šœ7˜7šœ;˜;KšžœPž™p——Kšœ˜—˜J™�——šŸ
œœœ˜/J˜J˜Jšœ2œ!˜YJšœœ+˜FJ˜—J˜�šŸœœœœœœ˜JJ˜J˜J˜J˜!Jšœ
œœd˜{šœ
˜
JšœTœ˜Z—šœœœ˜-JšœEœ ˜f—Jšžœ¶ #œž™Ü˜7JšœWœ™\—Jšœœœœ˜Jšœ! "˜CJšœ/ %˜TJšœ2˜2Jšœ%˜%Jšœ;˜;Jšœ'œ#˜MJšœ˜J™J™X—J˜�šŸœœœœ˜;J˜Jšœ
œœ ˜7Jšœœ˜Jšœ'œ#˜MJšœ˜J˜�——J™�™J˜�J˜�šœœœ ˜!J™8Jšœ# ™=Jšœ  ™'Jšœ 0™7Jšœ ™Jšœ H™MJ™J˜�—š	œœ
œœ
œ˜NJ™¢J™�JšÏfÐfsb™cš£ZÑcfs
˜dJšœ1™1Jšœk™k—Jš£[¤˜bJš£Y¤
˜cJš£Z¤˜eJš£Z¤
˜dJš£Z¤
˜gš£Ñbfs£¥£G¤˜eJ™H—Jš£Z¤˜eJš£Z¤
˜dJ𣥣¥£F¤˜gJš
£¥£¥£6¥£¥£¤	˜b𣥣¥£F¤˜pJšÐstÏs0¦™2—J˜——J˜�J˜™'K™	KšœÏr™—™'K™&Kšœ¨™—™&K™Kšœ¨y™…—™)K™nKšœ¨v™‚—™)Kšœ*™*Kšœ¨;™G—™*Kšœ0™0Kšœ¨5™A—™+K™6Kšœ¨ ™,—™,Kšœ¨™—K™�—�…—����:,��aC��