File: VoiceStreamBasicImpl.mesa
Copyright © 1986 by Xerox Corporation. All rights reserved.
This file contains part of the VoiceStream implementation.
Routines in this file provide basic client facilities such as
opening closing, reading, and writing voice streams.
Ades, April 25, 1986 3:21:45 pm PST
Swinehart, May 10, 1986 5:38:29 pm PDT
Last Edited by: Swinehart, April 14, 1983 10:48 am
Last Edited by: Ousterhout, March 8, 1983 11:37 amcompile
Last Edited by: L. Stewart, December 30, 1983 11:19 am
DIRECTORY
IO USING [noWhereStream, STREAM],
Jukebox USING [bytesPerChirp, CloseTune, Handle, pagesPerChirp, RunComponent, singlePktLength, EnergyRange, hangoverPackets],
PrincOps USING [ByteBltBlock],
PrincOpsUtils USING [ByteBlt],
Process USING [MsecToTicks, SetTimeout],
Rope USING [ROPE],
VM USING [AddressForPageNumber, Allocate, Free],
VoiceStream;
VoiceStreamBasicImpl: MONITOR LOCKS Lock
IMPORTS Jukebox, IO, PrincOpsUtils, Process, VM
EXPORTS VoiceStream =
BEGIN
See VoiceStream.mesa for documentation on the following things.
Lock: PUBLIC MONITORLOCK;
wholeTune: PUBLIC INT ← 100000000;
serverCondition: PUBLIC CONDITION;
client: PUBLIC CONDITION;
waitCondition: PUBLIC CONDITION;
closeCondition: PUBLIC CONDITION;
ioStream: PUBLIC IO.STREAMIO.noWhereStream;
vSList: PUBLIC VoiceStream.Handle ← NIL;
Error: PUBLIC ERROR[reason: VoiceStream.ErrorCode, rope: Rope.ROPE] = CODE;
DemonError: PUBLIC ERROR = CODE;
The following variables keep track of how many streams have been
used and how often waiting occurred.
nOpens: INT ← 0;
nWaits: INT ← 0;
Open: PUBLIC PROC [jukebox: Jukebox.Handle, proc: VoiceStream.NotifyProc ← NIL,
clientData: REF ANYNIL]
RETURNS [handle: VoiceStream.Handle] = {
ENABLE UNWIND => NULL;
buffer: REF VoiceStream.Buffer ← NIL;
handle ← NEW[VoiceStream.VSRecord ← [jukebox, NIL, NIL, NIL, NIL, NIL, NIL,
Bug, proc, FALSE, clientData, NIL, , FALSE]];
Process.SetTimeout[condition: @handle.newPiece, ticks: Process.MsecToTicks[400]];
FOR i:INTEGER IN [0..VoiceStream.buffersPerStream) DO
buffer ← NEW[VoiceStream.Buffer];
buffer.valid ← FALSE;
buffer.chirpSpace ← VM.Allocate[count: Jukebox.pagesPerChirp];
buffer.block.blockPointer ← LOOPHOLE[VM.AddressForPageNumber[buffer.chirpSpace.page]];
buffer.runData ← buffer.block.blockPointer + (Jukebox.bytesPerChirp/2);
buffer.next ← handle.firstIdleBuffer;
handle.firstIdleBuffer ← buffer;
ENDLOOP;
OpenLocked[handle];
RETURN [handle];
};
OpenLocked: ENTRY PROC [handle: VoiceStream.Handle] = {
ENABLE UNWIND => NULL;
handle.next ← vSList;
vSList ← handle;
nOpens ← nOpens + 1;
Invoke the server to prepare the buffers for actual use.
NOTIFY serverCondition;
};
Close: PUBLIC ENTRY PROC [handle: VoiceStream.Handle] = {
This procedure closes out a voice stream. It waits for
pending I/O to complete, then deallocates the stream.
ENABLE UNWIND => NULL;
buffer: REF VoiceStream.Buffer;
record: VoiceStream.Handle;
IO.PutF[ioStream, "Closing tune.\n"];
Make sure that the stream isn't already closed.
IF (handle.errorRope # NIL) AND (handle.errorCode = StreamClosed)
THEN ERROR Error[StreamClosed, handle.errorRope];
Output any partially full buffers to the jukebox.
FlushBuffer[handle];
Flush any pending pieces.
FlushProc[handle];
Flush any pending client buffers.
WHILE (handle.firstClientBuffer # NIL) DO
handle.firstClientBuffer.valid ← FALSE;
GiveServerBuffer[handle:handle];
ENDLOOP;
Wait for the server to get completely caught up. This code
also synchronizes with the server so we're sure the server
isn't touching the voice stream info anymore.
WHILE (handle.firstServerBuffer # NIL) AND (handle.errorRope = NIL) DO
NOTIFY serverCondition;
WAIT closeCondition;
ENDLOOP;
Close any tune that might be open.
IF handle.piece # NIL THEN {
IF handle.piece.tune # NIL THEN Jukebox.CloseTune[handle.jukebox, handle.piece.tune];
};
If there is a socket process, then signal it to die.
IF handle.connection # NIL THEN handle.connection.socket ← NIL;
Remove the VSRecord from our list, then de-allocate the spaces
for the buffers (everything else is taken care of by the garbage
collector.
IF vSList = handle THEN vSList ← handle.next
ELSE {
record ← vSList;
WHILE record.next # handle DO
IF record.next = NIL THEN ERROR Error[Bug, "Unexpected vSList end."];
record ← record.next;
ENDLOOP;
record.next ← handle.next;
};
WHILE handle.firstClientBuffer # NIL DO
buffer ← handle.firstClientBuffer;
handle.firstClientBuffer ← buffer.next;
VM.Free[buffer.chirpSpace];
ENDLOOP;
WHILE handle.firstServerBuffer # NIL DO
buffer ← handle.firstServerBuffer;
handle.firstServerBuffer ← buffer.next;
VM.Free[buffer.chirpSpace];
ENDLOOP;
WHILE handle.firstIdleBuffer # NIL DO
buffer ← handle.firstIdleBuffer;
handle.firstIdleBuffer ← buffer.next;
VM.Free[buffer.chirpSpace];
ENDLOOP;
Mark the VSRecord invalid.
handle.errorCode ← StreamClosed;
handle.errorRope ← "Can't use voice stream after it's closed.";
handle.jukebox ← NIL;
BROADCAST client;
BROADCAST waitCondition;
};
Get: PUBLIC ENTRY PROC [handle: VoiceStream.Handle, maxSilentBytes: NAT, block: PrincOps.ByteBltBlock, wait: BOOLFALSE]
RETURNS [silence: NAT ← 0, bytesTransferred: NAT ← 0, keyIndex: NAT ← 0] = {
ENABLE UNWIND => NULL;
buffer: REF VoiceStream.Buffer;
runSize: NAT;
DO
1) Aquire a non-empty chirp
If the server isn't doing its job, then we may have to wait here to get a chirp. This shouldn't happen and should probably be reported. Rather than wait, we should play silence and try again later in order to keep the protocol inviolate.
WHILE (handle.firstClientBuffer = NIL) DO
IF handle.errorRope # NIL THEN ERROR Error[handle.errorCode, handle.errorRope];
IF handle.piece = NIL THEN {
IF handle.proc # NIL AND NOT handle.notified THEN {
handle.notified ← TRUE;
handle.proc[handle, handle.clientData];
};
BROADCAST waitCondition;
RETURN;
};
nWaits ← nWaits + 1;
IF wait THEN WAIT client
ELSE RETURN;
ENDLOOP;
buffer ← handle.firstClientBuffer;
handle.notified ← FALSE;
keyIndex ← buffer.keyIndex;
If the stream is currently going the wrong way, then just
return immediately whith whatever has been accumulated. Typically this is a RETURN[0, 0].
IF buffer.toJukebox THEN RETURN;
If the current piece is being flushed, then just give the buffers
back to the server immediately (ignore the data).
IF handle.piece.flush THEN {
handle.firstClientBuffer.valid ← FALSE;
GiveServerBuffer[handle: handle];
LOOP;
};
If presently recording, then quietly return. Typically this is a RETURN[0, 0].
IF buffer.toJukebox THEN RETURN;
If we have used up all of this chirp, then give it back and get the next chirp. This should be done at the end of the code, not the beginning.
IF buffer.bytesAccountedFor >= Jukebox.bytesPerChirp THEN {
IO.PutF[ioStream, "Got chirp %d.\n", IO.int[buffer.chirp]];
GiveServerBuffer[handle: handle];
LOOP;
};
WITH curr: buffer.runData.runArray[buffer.runIndex] SELECT FROM
silence =>
{ silenceAmount: CARDINAL;
IF maxSilentBytes=0 THEN RETURN;
 runSize ← curr.length;
 silenceAmount ← MIN[runSize, maxSilentBytes, Jukebox.bytesPerChirp - buffer.bytesAccountedFor];
silence ← silence + silenceAmount;
curr.length ← runSize - silenceAmount;
IF curr.length=0 THEN
{ buffer.runIndex𡤋uffer.runIndex+1;
 buffer.playedBytes𡤀
};
buffer.bytesAccountedFor ← buffer.bytesAccountedFor + silenceAmount;
handle.piece.packetsSinceLastNonSilence ← handle.piece.packetsSinceLastNonSilence + (silenceAmount+Jukebox.singlePktLength/2)/Jukebox.singlePktLength;
maxSilentBytes ← maxSilentBytes - silenceAmount;
};
soundEnergy =>
{ runSize ← NARROW[buffer.runData.runArray[buffer.runIndex+1],
Jukebox.RunComponent[soundLength]].length;
handle.piece.packetsSinceLastNonSilence ← IF curr.energy <= buffer.runData.ambientLevel THEN handle.piece.packetsSinceLastNonSilence + (runSize+Jukebox.singlePktLength/2)/Jukebox.singlePktLength ELSE 0;
IF handle.piece.packetsSinceLastNonSilence > Jukebox.hangoverPackets
means packet should be treated as silence that should not be transmitted
THEN
{ silenceAmount: CARDINAL;
IF maxSilentBytes=0 THEN RETURN;
silenceAmount ← MIN[runSize, maxSilentBytes, Jukebox.bytesPerChirp - buffer.bytesAccountedFor];
buffer.block.startIndex ← buffer.block.startIndex + silenceAmount;
buffer.bytesAccountedFor ← buffer.bytesAccountedFor + silenceAmount;
silence ← silence + silenceAmount;
buffer.runData.runArray[buffer.runIndex+1] ← [soundLength[runSize - silenceAmount]];
IF NARROW[buffer.runData.runArray[buffer.runIndex+1], Jukebox.RunComponent[soundLength]].length=0 THEN
{ buffer.runIndex𡤋uffer.runIndex+2;
buffer.playedBytes𡤀
};
maxSilentBytes ← maxSilentBytes - silenceAmount;
}
ELSE -- really want to play this back
{ voiceAmount: CARDINAL;
origStopIndex: CARDINAL;
count: CARDINAL;
maxSilentBytes ← 0;
once sound found, stop on further occurences of silence
voiceAmount ← MIN[runSize, block.stopIndexPlusOne - block.startIndex, Jukebox.bytesPerChirp - buffer.bytesAccountedFor];
IF runSize # voiceAmount AND curr.energy <= buffer.runData.ambientLevel THEN
we have added too much to packetsSinceLastNonSilence: this is never exact in the face of variable length soundLengths and partial usage of singlePkts, but we'd like to keep it near as possible
handle.piece.packetsSinceLastNonSilence ← handle.piece.packetsSinceLastNonSilence - ((runSize - voiceAmount)+Jukebox.singlePktLength/2)/Jukebox.singlePktLength;
origStopIndex ← block.stopIndexPlusOne;
block.stopIndexPlusOne ← block.startIndex + voiceAmount;
count ← PrincOpsUtils.ByteBlt[from: buffer.block, to: block];
IF count # voiceAmount THEN ERROR;
block.stopIndexPlusOne ← origStopIndex;
block.startIndex ← block.startIndex + voiceAmount;
buffer.block.startIndex ← buffer.block.startIndex + voiceAmount;
buffer.bytesAccountedFor ← buffer.bytesAccountedFor + voiceAmount;
buffer.runData.runArray[buffer.runIndex+1] ← [soundLength[runSize - voiceAmount]];
IF NARROW[buffer.runData.runArray[buffer.runIndex+1], Jukebox.RunComponent[soundLength]].length=0 THEN
{ buffer.runIndex𡤋uffer.runIndex+2;
buffer.playedBytes𡤀
};
bytesTransferred ← bytesTransferred + voiceAmount;
IF block.startIndex >= block.stopIndexPlusOne THEN {
IF buffer.bytesAccountedFor >= Jukebox.bytesPerChirp THEN {
IO.PutF[ioStream, "Got chirp %d.\n", IO.int[buffer.chirp]];
GiveServerBuffer[handle: handle];
};
handle.action ← TRUE;
RETURN;
}
}
};
singlePkt =>
{ handle.piece.packetsSinceLastNonSilence ← IF curr.energy <= buffer.runData.ambientLevel THEN handle.piece.packetsSinceLastNonSilence + 1 ELSE 0;
IF handle.piece.packetsSinceLastNonSilence > Jukebox.hangoverPackets
means packet should be treated as silence that should not be transmitted
THEN
{ silenceAmount: CARDINAL;
IF maxSilentBytes=0 THEN RETURN;
runSize ← Jukebox.singlePktLength - buffer.playedBytes;
silenceAmount ← MIN[runSize, maxSilentBytes, Jukebox.bytesPerChirp - buffer.bytesAccountedFor];
buffer.block.startIndex ← buffer.block.startIndex + silenceAmount;
buffer.bytesAccountedFor ← buffer.bytesAccountedFor + silenceAmount;
buffer.playedBytes ← buffer.playedBytes + silenceAmount;
silence ← silence + silenceAmount;
IF buffer.playedBytes = Jukebox.singlePktLength THEN
{ buffer.runIndex𡤋uffer.runIndex+1;
 buffer.playedBytes𡤀
};
maxSilentBytes ← maxSilentBytes - silenceAmount;
}
ELSE -- really want to play this back
{ voiceAmount: CARDINAL;
origStopIndex: CARDINAL;
count: CARDINAL;
maxSilentBytes ← 0;
runSize ← Jukebox.singlePktLength - buffer.playedBytes;
voiceAmount ← MIN[runSize, block.stopIndexPlusOne - block.startIndex, Jukebox.bytesPerChirp - buffer.bytesAccountedFor];
IF voiceAmount < Jukebox.singlePktLength/2 AND curr.energy <= buffer.runData.ambientLevel THEN
we incremented packetsSinceLastNonSilence incorrectly: if we take things out of the chirp exclusively in less than Jukebox.singlePktLength/2 lengths we'll get our counting wrong, but we'll at least try to be roughly right most of the time
handle.piece.packetsSinceLastNonSilence ← handle.piece.packetsSinceLastNonSilence - 1;
origStopIndex ← block.stopIndexPlusOne;
block.stopIndexPlusOne ← block.startIndex + voiceAmount;
count ← PrincOpsUtils.ByteBlt[from: buffer.block, to: block];
IF count # voiceAmount THEN ERROR;
block.stopIndexPlusOne ← origStopIndex;
block.startIndex ← block.startIndex + voiceAmount;
buffer.block.startIndex ← buffer.block.startIndex + voiceAmount;
buffer.bytesAccountedFor ← buffer.bytesAccountedFor + voiceAmount;
buffer.playedBytes ← buffer.playedBytes + voiceAmount;
IF buffer.playedBytes = Jukebox.singlePktLength THEN
{ buffer.runIndex𡤋uffer.runIndex+1;
buffer.playedBytes𡤀
};
bytesTransferred ← bytesTransferred + voiceAmount;
IF block.startIndex >= block.stopIndexPlusOne THEN {
IF buffer.bytesAccountedFor >= Jukebox.bytesPerChirp THEN {
IO.PutF[ioStream, "Got chirp %d.\n", IO.int[buffer.chirp]];
GiveServerBuffer[handle: handle];
};
handle.action ← TRUE;
RETURN;
}
}
};
ENDCASE => ERROR;
handle.action ← TRUE;
ENDLOOP;
};
Put: PUBLIC ENTRY PROC [handle: VoiceStream.Handle, silentBytes: NAT, block: PrincOps.ByteBltBlock, energy: CARDINAL] RETURNS [bytesTransferred: NAT ← 0] = {
This procedure adds the bytes from block to the end of the
voice stream.
ENABLE UNWIND => NULL;
buffer: REF VoiceStream.Buffer;
energy ← energy/4;
since we store energies as 14 bit unsigned numbers, but they come in as cardinals
WHILE silentBytes > 0 OR block.startIndex < block.stopIndexPlusOne
DO
WHILE handle.firstClientBuffer = NIL DO
IF handle.errorRope # NIL THEN ERROR Error[handle.errorCode, handle.errorRope];
IF handle.piece = NIL THEN {
IF handle.proc # NIL AND NOT handle.notified THEN {
handle.notified ← TRUE;
handle.proc[handle, handle.clientData];
};
BROADCAST waitCondition;
RETURN;
};
WAIT client;
ENDLOOP;
If the stream is currently going the wrong way, then just
return immediately. Typically this is a RETURN[0].
buffer ← handle.firstClientBuffer;
handle.notified ← FALSE;
IF NOT buffer.toJukebox THEN RETURN;
If the current piece is being flushed, then get rid of the current buffer
(throw it away if it's invalid, otherwise fill it with zeroes).
IF handle.piece.flush THEN {
IF handle.firstClientBuffer.valid THEN FlushBuffer[handle]
ELSE GiveServerBuffer[handle: handle];
LOOP;
};
If not presently recording, then quietly return. Typically this is a RETURN[0].
IF NOT buffer.toJukebox THEN RETURN;
If we have used up all of this chirp, then give it back and get the next chirp. This should be done at the end of the code, not the beginning.
IF buffer.bytesAccountedFor >= Jukebox.bytesPerChirp THEN {
IO.PutF[ioStream, "Got chirp %d.\n", IO.int[buffer.chirp]];
GiveServerBuffer[handle: handle];
LOOP;
};
SELECT TRUE FROM
silentBytes>0 => {
silenceAmount: CARDINALMIN[silentBytes, Jukebox.bytesPerChirp - buffer.bytesAccountedFor];
handle.piece.packetsSinceLastNonSilence ← handle.piece.packetsSinceLastNonSilence + (silenceAmount+(Jukebox.singlePktLength/2))/Jukebox.singlePktLength;
IF buffer.runData.runArray[buffer.runIndex].elementType ~= silence THEN
last thing placed in chirp was non-silent
{ buffer.runIndex ← buffer.runIndex +
(IF buffer.runData.runArray[buffer.runIndex].elementType = soundEnergy
THEN 2 ELSE 1);
 buffer.runData.runArray[buffer.runIndex]← [silence[0]]
};
silentBytes ← silentBytes - silenceAmount;
buffer.runData.runArray[buffer.runIndex]← [silence[NARROW[buffer.runData.runArray[buffer.runIndex], Jukebox.RunComponent[silence]].length+silenceAmount]];
buffer.bytesAccountedFor ← buffer.bytesAccountedFor + silenceAmount;
};
block.startIndex < block.stopIndexPlusOne => {
IF energy <= buffer.runData.ambientLevel
THEN
{ transferAmount: CARDINALMIN[block.stopIndexPlusOne - block.startIndex,
Jukebox.bytesPerChirp - buffer.bytesAccountedFor];
handle.piece.packetsSinceLastNonSilence ← handle.piece.packetsSinceLastNonSilence + (transferAmount+(Jukebox.singlePktLength/2))/Jukebox.singlePktLength
}
ELSE handle.piece.packetsSinceLastNonSilence ← 0;
beware: this bit of the code assumes blocks of sound passed to Put will not exceed 30ms in length. If they do it can happen that blocks will be discarded because of low energy sooner than hangoverPackets from when the last over-threshold sound occured. Such a radical change is unlikely to occur to VoiceStreams and handling it here would make the code even more obscure.
IF handle.piece.packetsSinceLastNonSilence > Jukebox.hangoverPackets
we want to throw away this sound, because it is now more than the hangover time since a packet with sufficient energy occured
THEN
{ silenceAmount: CARDINALMIN[block.stopIndexPlusOne - block.startIndex, Jukebox.bytesPerChirp - buffer.bytesAccountedFor];
IF buffer.runData.runArray[buffer.runIndex].elementType ~= silence THEN
last thing placed in chirp was non-silent
{ buffer.runIndex ← buffer.runIndex +
(IF buffer.runData.runArray[buffer.runIndex].elementType = soundEnergy
THEN 2 ELSE 1);
 buffer.runData.runArray[buffer.runIndex]← [silence[0]]
};
buffer.runData.runArray[buffer.runIndex]← [silence[NARROW[buffer.runData.runArray[buffer.runIndex], Jukebox.RunComponent[silence]].length+silenceAmount]];
buffer.bytesAccountedFor ← buffer.bytesAccountedFor + silenceAmount;
bytesTransferred ← bytesTransferred + silenceAmount;
block.startIndex ← block.startIndex + silenceAmount;
alter only the source count, to look as though we have taken the sound
IF block.startIndex >= block.stopIndexPlusOne THEN
{ IF buffer.bytesAccountedFor >= Jukebox.bytesPerChirp THEN
{ -- IO.PutF[ioStream, "Put chirp %d.\n", IO.int[buffer.chirp]];
GiveServerBuffer[handle: handle];
};
handle.action ← TRUE;
RETURN
}
}
ELSE
{
voiceAmount: CARDINALMIN[block.stopIndexPlusOne - block.startIndex, Jukebox.bytesPerChirp - buffer.bytesAccountedFor];
origStopIndex: CARDINAL ← block.stopIndexPlusOne;
count: CARDINAL;
block.stopIndexPlusOne ← block.startIndex + voiceAmount;
count ← PrincOpsUtils.ByteBlt[from: block, to: buffer.block];
IF count # voiceAmount THEN ERROR;
block.stopIndexPlusOne ← origStopIndex;
IF voiceAmount > 0 THEN buffer.valid ← TRUE;
block.startIndex ← block.startIndex + voiceAmount;
buffer.block.startIndex ← buffer.block.startIndex + voiceAmount;
buffer.bytesAccountedFor ← buffer.bytesAccountedFor + voiceAmount;
bytesTransferred ← bytesTransferred + voiceAmount;

IF ~(buffer.runData.runArray[buffer.runIndex].elementType = silence AND
NARROW[buffer.runData.runArray[buffer.runIndex], Jukebox.RunComponent[silence]].length=0) THEN buffer.runIndex ← buffer.runIndex +(IF buffer.runData.runArray[buffer.runIndex].elementType = soundEnergy THEN 2 ELSE 1);
only false if this is first item to be placed in this chirp
IF voiceAmount = Jukebox.singlePktLength THEN buffer.runData.runArray[buffer.runIndex] ← [singlePkt[energy]]
ELSE
{ buffer.runData.runArray[buffer.runIndex] ← [soundEnergy[energy]];
 buffer.runData.runArray[buffer.runIndex+1] ← [soundLength[voiceAmount]]
};

IF block.startIndex >= block.stopIndexPlusOne THEN {
IF buffer.bytesAccountedFor >= Jukebox.bytesPerChirp THEN {
IO.PutF[ioStream, "Put chirp %d.\n", IO.int[buffer.chirp]];
GiveServerBuffer[handle: handle];
};
handle.action ← TRUE;
RETURN;
};
}
};
ENDCASE => ERROR;
handle.action ← TRUE;
ENDLOOP;
};
AddPiece: PUBLIC ENTRY PROC [handle: VoiceStream.Handle, tuneId: INT,
firstByte: INT, nBytes: INT, create: BOOLEAN,
playback: BOOLEANTRUE, keyIndex: NAT ← 0, flush: BOOLEANFALSE, ambientLevel: Jukebox.EnergyRange ← 0] = {
This routine allocates another piece descriptor and adds it to the
list for the voice stream.
ENABLE UNWIND => NULL;
piece, p2: REF VoiceStream.Piece;
IF handle.errorRope # NIL
THEN ERROR Error[handle.errorCode, handle.errorRope];
IF flush THEN FlushProc[handle];
piece ← NEW[VoiceStream.Piece ← [tuneId, create, firstByte, nBytes,
NIL, playback, keyIndex, NIL, FALSE, ambientLevel, Jukebox.hangoverPackets]];
IF handle.piece = NIL THEN handle.piece ← piece
ELSE {
p2 ← handle.piece;
WHILE p2.next # NIL DO p2 ← p2.next ENDLOOP;
p2.next ← piece;
};
ioStream.PutF["%s: size %d\n", IO.rope[IF playback THEN "Playback" ELSE "Record"],
IO.int[nBytes]];
NOTIFY serverCondition;
};
FlushPieces: PUBLIC ENTRY PROC [handle: VoiceStream.Handle] = {
ENABLE UNWIND => NULL;
FlushProc[handle];
};
FlushProc: INTERNAL PROC [handle: VoiceStream.Handle] = {
This routine flushes any unused voice info in a stream.
This is done by marking all the pieces as "flushed". Then,
various routines see the flush flag and ignore information.
Buffers currently waiting to be written to disk will not
be flushed, but everything else will be. It isn't safe
synchronization-wise for us to just remove all the buffers
and pieces, hence the use of the flag.
p: REF VoiceStream.Piece ← handle.piece;
WHILE p # NIL DO
p.flush ← TRUE;
p ← p.next;
ENDLOOP;
BROADCAST client;
BROADCAST waitCondition;
};
IsEmpty: PUBLIC PROC [handle: VoiceStream.Handle] RETURNS [BOOLEAN] = {
Figure out whether the socket process has used up all the
available pieces.
IF handle.firstClientBuffer # NIL THEN RETURN[FALSE];
IF handle.piece # NIL THEN RETURN[FALSE];
RETURN[TRUE];
};
WaitEmpty: PUBLIC ENTRY PROC [handle: VoiceStream.Handle] = {
Just wait until the stream empties completely.
ENABLE UNWIND => NULL;
WHILE TRUE DO
IF handle.errorRope # NIL THEN RETURN;
IF (handle.firstClientBuffer = NIL) AND (handle.piece = NIL) THEN RETURN;
WAIT waitCondition;
ENDLOOP;
};
Check: PUBLIC ENTRY PROC [handle: VoiceStream.Handle]
RETURNS[BOOLEAN] = {
If there are any errors pending for the given voice stream,
they are signalled immediately. If there are no errors and
there is data ready for playback, then TRUE is returned.
Otherwise, FALSE is returned.
ENABLE UNWIND => NULL;
IF handle.errorRope # NIL THEN
ERROR Error[handle.errorCode, handle.errorRope];
IF handle.firstClientBuffer = NIL THEN RETURN[FALSE];
IF handle.firstClientBuffer.toJukebox THEN RETURN[FALSE];
RETURN[TRUE];
};
GiveServerBuffer: INTERNAL PROC [handle: VoiceStream.Handle] = {
This routine passes the leading buffer to the server, and
activates the server.
buffer, b2: REF VoiceStream.Buffer;
buffer ← handle.firstClientBuffer;
handle.firstClientBuffer ← buffer.next;
buffer.next ← NIL;
IF handle.firstServerBuffer = NIL THEN handle.firstServerBuffer ← buffer
ELSE {
b2 ← handle.firstServerBuffer;
WHILE b2.next # NIL DO b2 ← b2.next ENDLOOP;
b2.next ← buffer;
};
NOTIFY serverCondition;
};
FlushBuffer: PUBLIC INTERNAL PROC [handle: VoiceStream.Handle] = {
If there is a partially-filled leading client buffer, this
routine pads it with zeros and sends it to the server.
buffer: REF VoiceStream.Buffer;
buffer ← handle.firstClientBuffer;
IF buffer = NIL THEN RETURN;
IF ~buffer.toJukebox THEN RETURN;
IF buffer.bytesAccountedFor IN (0..Jukebox.bytesPerChirp) THEN {
IF buffer.runData.runArray[buffer.runIndex].elementType ~= silence THEN
last thing placed in chirp was non-silent
{ buffer.runIndex ← buffer.runIndex + (IF buffer.runData.runArray[buffer.runIndex].elementType = soundEnergy THEN 2 ELSE 1);
 buffer.runData.runArray[buffer.runIndex] ← [silence[0]]
};
buffer.runData.runArray[buffer.runIndex]← [silence[NARROW[buffer.runData.runArray[buffer.runIndex], Jukebox.RunComponent[silence]].length+(Jukebox.bytesPerChirp - buffer.bytesAccountedFor)]];
buffer.bytesAccountedFor ← Jukebox.bytesPerChirp; -- just for purity
GiveServerBuffer[handle: handle];
};
};
END.
Last Edited by: L. Stewart, March 25, 1983 3:54 pm, VoiceStream change
L. Stewart, April 5, 1983 2:38 pm, Tioga formatting, rundata
L. Stewart, April 11, 1983 1:06 pm, bug fixing in rundata
Last Edited by: L. Stewart, April 19, 1983 3:17 pm, Silence encoding
L. Stewart, June 4, 1983 5:42 pm, call notifyProc only once
L. Stewart, May 10, 1986 4:06:25 pm PDT, Cedar 5, VoiceStreamBasicImpl, AddPiece, FlushPieces, FlushProc, IsEmpty, WaitEmpty, Check, L, EXPORTS
Swinehart, May 10, 1986 4:03:07 pm PDT
Convert to new communication package
changes to: BEGIN, vSList, Open, OpenLocked, Close, Get, Put, GiveServerBuffer, FlushBuffer