DIRECTORY
BasicTime USING [ Update, Now, Period ],
IO,
Lark USING [ bStar, bThorp, ConnectionSpec, CommandEvent, CommandEvents, CommandEventSequence, Device, disabled, EchoParameters, EchoParameterRecord, enabled, endNum, Event, Hertz, KeyTable, Milliseconds, o3i1, o2i2, o1i1, Passel, reset, SHHH ],
LarkSmarts,
Log USING [ ProblemFR, Report, SLOG ],
Nice,
PlayOps USING [ PlayString, BeepProc ],
Process USING [ Detach, EnableAborts, MsecToTicks, SetTimeout ],
Rope USING [ Fetch, Length, ROPE ],
RPC USING [ CallFailed ],
ThNet USING [ pd ],
ThPartyPrivate USING [ SmartsData ],
Thrush USING[ H, pERROR, ROPE, SHHH, SmartsHandle, ThHandle ],
ThSmartsPrivate
USING [
ConvDesc, GetConvDesc, HookState, LarkInfo, LarkState, LarkStateSpec, LSwitches, LState, Note, ProgressTones, RingMode, RingEnable, SetStdRingInfo, SmartsInfo, TerminalType, ToneSpec, ToneSpecRec ],
TU USING [ RefAddr ]
;
Declarations
ConvDesc: TYPE = ThSmartsPrivate.ConvDesc;
H: PROC[r: REF] RETURNS[Thrush.ThHandle] = INLINE {RETURN[Thrush.H[r]]; };
LarkInfo: TYPE = ThSmartsPrivate.LarkInfo;
LarkState: TYPE = ThSmartsPrivate.LarkState;
SmartsData: TYPE = ThPartyPrivate.SmartsData;
SmartsInfo: TYPE = ThSmartsPrivate.SmartsInfo;
SmartsHandle: TYPE = Thrush.SmartsHandle;
TerminalType: TYPE = ThSmartsPrivate.TerminalType;
ROPE: TYPE = Thrush.ROPE;
firstTone: LarkState = FIRST[ThSmartsPrivate.ProgressTones];
bStar: Lark.Event = Lark.bStar;
bThorp: Lark.Event = Lark.bThorp;
enabled: Lark.Event = Lark.enabled;
endNum: Lark.Event = Lark.endNum;
disabled: Lark.Event = Lark.disabled;
reset: Lark.Event = Lark.reset;
larkRegistry: ROPE ← ".Lark";
PD:
TYPE =
RECORD [
waitForTelco: CARDINAL ← 500,
telcoMinOn: CARDINAL ← 60,
telcoMinOff: CARDINAL ← 60,
backDoorOH: BOOL←FALSE,
echoControl: BOOL←TRUE,
autoGVUpdate: BOOL←FALSE, -- If FALSE, operator must manually update true GV database.
tonesLast: BOOL←FALSE, -- sets up alternate lark setup situation in supervisor loop
ringsInvalid: BOOL←TRUE, -- set to cause recreation of standard ring tunes
tonesVolume: CARDINAL ← 2,
defaultRingVolume: CARDINAL ← 2,
subduedVolumeInterval: CARDINAL𡤁,
feepVolume: CARDINAL ← 0
];
pd: REF PD ← NEW[PD←[]];
callTimeoutOK: BOOL←FALSE; -- set to keep Thrush alive when debugging a Lark.
ToneSpec: TYPE = ThSmartsPrivate.ToneSpec;
ToneSpecRec: TYPE = ThSmartsPrivate.ToneSpecRec;
Note: TYPE = ThSmartsPrivate.Note;
State tables
LSwitches: TYPE = ThSmartsPrivate.LSwitches;
LState: TYPE = ThSmartsPrivate.LState;
lDevs:
ARRAY LSwitches
OF Lark.Device = [
crossBar, offHookRelay, aRelay, sideTone, ringEnable, revertRelay, revertHookswitch, led, spMode, crossBar--random...not used-- ];
lStateForLetter:
ARRAY
CHAR['A..'Z]
OF LSwitches = [
none, none, none, none, none, -- A to E
revert, revertHook, hook, aSwitch, hook, none, led, -- F to L
none, none, none, none, none, -- M to Q
ringO, sideTone, spMode, none, none, none, none, none, -- R to Y
xBarAll -- Z --
];
LSTrans:
TYPE = {
nop, -- nothing to do
set, -- enter specified state (usu. step to recovery) without taking any other actions.
zap, zpu, -- reset Lark hardware (u means unconnect first)
trk, tkn, -- Set for electronic phone connection (n means silence tones first)
frd, frn, -- Trunk-to-network forwarding versions of trk, tkn (frn probably doesn't exist; wrong end <<Sep. FD/BD>>)
tlk, -- like supervision, but must also adjust switching.
sup, spn, -- supervision, OK to change connection, key table. (n means silence tones first)
ksp, -- key supervision, OK to change key table.
sgl, sgn, -- Do trunk signalling (n means silence tones first)
fls, -- Flash the phone line
rng, rgu, -- Set for ringing (u means unconnect first, r means repeating tone)
dia, diu, -- Set for dial tone (tones should be more generic and user-programmable than this!)
rbk, rbu, -- Set for ring back
bzy, bzu, -- Set for busy tone
err, eru, -- Set for error tone
sil, -- silence tones, ksp obtains
fai, -- enter failed state, by Smarts-level request. Don't complain, just do it. Make sure process goes away.
rec, -- move from failed state to recovering state, but complain to caller that Lark has failed, via signal.
X -- invalid transition; complain, then remain in present state (go idle?)
};
lsTrans:
ARRAY LarkState
OF
ARRAY LarkState
OF LSTrans = [[
non idl tlk sig trk fwd fls fai rec rng shh dia rbk bzy err ←new old \/
nop, zap, X, X, X, X, X, X, X, X, X, X, X, X, X ],[-- non (none)
X, nop, spn, sgl, trk, frd, X, fai, X, rng, nop, dia, rbk, bzy, err ],[-- idl (idle)
X, zpu, sup, X, X, X, X, fai, X, rgu, nop, diu, rbu, bzu, eru ],[-- tlk (talking)
X, zap, X, ksp, trk, frd, X, fai, X, X, nop, X, X, X, X ],[-- sig (trkSignalling)
X, zap, X, X, ksp, X, fls, fai, X, X, nop, X, X, X, X ],[-- trk (trkTalking)
X, zpu, X, X, X, sup, X, fai, X, X, nop, diu, rbu, bzu, eru ],[-- fwd (trkForwarding)
X, zap, X, X, trk, X, sup, fai, X, X, nop, X, X, X, X ],[-- fls (trkFlash)
set, rec, rec, rec, rec, rec, rec, set, set, rec, rec, rec, rec, rec, rec ],[-- fai (failed)
set, nop, nop, nop, nop, nop, nop, nop, nop, nop, nop, nop, nop, nop, nop ],[-- rec (recovering)
X, zap, spn, sgn, tkn, frn, X, fai, X, ksp, sil, dia, rbk, bzy, err ],[-- rng (ringing)
X, zap, tlk, sgl, trk, frd, X, fai, X, rng, ksp, dia, rbk, bzy, err ],[-- shh (silence)
X, zap, spn, sgn, tkn, frn, X, fai, X, rng, sil, ksp, rbk, bzy, err ],[-- dia (dialTone)
X, zap, spn, sgn, tkn, frn, X, fai, X, rng, sil, dia, ksp, bzy, err ],[-- rbk (ringBack)
X, zap, spn, sgn, tkn, frn, X, fai, X, rng, sil, dia, rbk, ksp, err ],[-- bzy (busyTone)
X, zap, spn, sgn, tkn, frn, X, fai, X, rng, sil, dia, rbk, bzy, ksp ] -- err (errorTone)
];
Subtransition codes and tables
TDisconn: TYPE = { X, disconnect };
tDisconn: ARRAY LSTrans OF TDisconn = [ -- zpu, rgu, diu, rbu, bzu, eru
X, X, X, disconnect, X, X, X, X, X, X, X, X, X, X, X, X, disconnect, X, disconnect, X, disconnect, X, disconnect, X, disconnect, X, X, X, X ];
TDoTones: TYPE = { X, doTones, stopTones };
tDoTones: ARRAY LSTrans OF TDoTones = [ -- rng, rgu, dia, diu, rbk, rbu, bzy, bzu, err, eru; tkn, spn, sgn, sil
X, X, X, X, X, stopTones, X, X, X, X, stopTones, X, X, stopTones, X, doTones, doTones, doTones, doTones, doTones, doTones, doTones, doTones, doTones, doTones, stopTones, X, X, X ];
THookState: TYPE = { X, reset, spkrTrans };
tHookState: ARRAY LSTrans OF THookState = [ -- zap, zpu; trk, tkn, tlk, spn, fls, dia, diu, rbk, rbu, bzy, bzu, err, eru, sil
X, X, reset, reset, spkrTrans, spkrTrans, X, X, spkrTrans, X, spkrTrans, X, X, X, spkrTrans, X, X, spkrTrans, spkrTrans, spkrTrans, spkrTrans, spkrTrans, spkrTrans, spkrTrans, spkrTrans, spkrTrans, X, X, X ];
TSwitch: TYPE = { X, switch, switchIfDiff };
tSwitch: ARRAY LSTrans OF TSwitch = [-- zap, zpu, trk, tkn, frd, frn, tlk, spn, sgl, sgn, fls; rng, rgu, dia, diu, rbk, rbu, bzy, bzu, err, eru
X, X, switch, switch, switch, switch, switch, switch, switch, X, switch, X, switch, switch, switch, switchIfDiff, switchIfDiff, switchIfDiff, switchIfDiff, switchIfDiff, switchIfDiff, switchIfDiff, switchIfDiff, switchIfDiff, switchIfDiff, switch, X, X, X ];
TSetKey: TYPE = { X, setKey };
tSetKey: ARRAY LSTrans OF TSetKey = [
-- trk, tkn, frd, frn, tlk, sup, spn, ksp, sgl, sgn, fls, rng, rgu, dia, diu, rbk, rbu, bzy, bzu, err, eru, sil
X, X, X, X, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, setKey, X, X, X ];
Internal Procedures
IF stateChanged AND ThNet.pd.debug THEN
Log.Report[IO.PutFR["<%s>", QuickState[newState]], $LarkDetailed, info];
LarkSupervisor:
PROCEDURE[ info: LarkInfo, sInfo: SmartsInfo ] = {
In a loop, keep the state of the Lark up to date. Awakens itself whenever any pending
tone is otherwise likely to time out. Awakened by EnterLarkState whenever the state
of tones, switches, and the like might have to change.
sInfo is the SmartsInfo in use when the process was initiated. It's used to report errors, but bear in mind that it may or may not be the one in effect when a particular complaint occurs.
ENABLE UNWIND => NULL;
ringTune: ToneSpec←NIL;
notes: LIST OF Note←NIL;
waitTime: INTEGER ← 0;
req: REF;
GetAction:
ENTRY
PROC [info: LarkInfo]
RETURNS [ref:
REF←
NIL] =
INLINE {
IF info.larkState=failed OR info.larkState=recovering THEN { info.newActions←NIL; ringTune←NIL; notes←NIL; }
ELSE refqueueLarkAction[info];
};
TRUSTED { Process.EnableAborts[@info.stateChange]; };
WHILE (req←GetAction[info])#
NIL
OR notes#
NIL
DO {
-- Deal with communications failure.
ENABLE {
RPC.CallFailed =>
IF callTimeoutOK
THEN
RESUME
ELSE {
LarkProblem["%g: Call Failed", sInfo]; GOTO Failed; };
ABORTED => {
LarkProblem["%g: LarkSupervisor aborted", sInfo]; GOTO Failed; };
};
flashWait: BOOL←FALSE;
newTones: BOOL←FALSE;
DoTones:
PROC[] = {
-- Does one tone from current list of tones
note: Note;
IF ringTune=NIL OR notes=NIL THEN { newTones←FALSE; RETURN; };
Log.SLOG[100000B];
IF waitTime=0 THEN waitTime ← ringTune.totalTime;
IF newTones THEN waitTime ← waitTime-2000;
IF ~ringTune.oneRing THEN continuingTones ← ttD;
note←notes.first;
notes←notes.rest;
[]←info.interface.GenerateTones[shh: info.shh, f1: note.f1, f2: note.f2, modulation: 0, repetitions: note.repetitions,
on: note.on, off: note.off, waveTable: ringTune.volume, queueIt: ~newTones, notify: [nothing, 0C]];
newTones←FALSE;
};
IF req#NIL THEN Log.SLOG[100000B];
IF req#
NIL
THEN
WITH req
SELECT
FROM
d:
REF ADisconnectType => {
info.interface.Disconnect[ shh: info.shh, buffer: out1];
info.interface.Disconnect[ shh: info.shh, buffer: in1];
};
w: REF AFlashWaitType => { flashWait←TRUE; waitTime ← 600; };
toneSpec: ToneSpec => {
ringTune←toneSpec; notes←ringTune.notes; newTones←TRUE;
IF ~pd.tonesLast THEN DoTones[];
};
a:
REF ANoTonesType => {
ringTune←NIL; notes←NIL;
[]←info.interface.GenerateTones[shh: info.shh, f1: 0, f2: 0, modulation: 0, repetitions: 0, on:0, off: 0,
waveTable: 0, queueIt: FALSE, notify: [nothing, 0C]];
};
echoParameters: Lark.EchoParameters =>
[]←info.interface.EchoSupression[shh: info.shh, echo: echoParameters];
commands: Lark.CommandEvents =>
IF commands#
NIL
THEN
IF commands[0].device=touchPad
THEN {
[]←info.interface.GenerateTones[
info.shh, 0, 0, 0, pd.waitForTelco, 0, 1, 3, FALSE, [nothing, 0C]];
[]←info.interface.Feep[shh: info.shh, on: pd.telcoMinOn, off: pd.telcoMinOff, notify: [tones, 'F],
waveTable: pd.feepVolume, queueIt: TRUE, events: commands];
}
ELSE info.interface.Commands[ info.shh, commands ];
keyTable: Lark.KeyTable => info.interface.SetKeyTable[shh: info.shh, table: keyTable];
spec: Lark.ConnectionSpec => {
Log.SLOG[100000B];
spec.buffer ← out1;
info.interface.Connect[shh: info.shh, specs: spec ];
Connect output buffer
spec.buffer ← in1;
info.interface.Connect[shh: info.shh, specs: spec ];
};
ENDCASE;
{
moreTones: BOOL←FALSE;
WaitQ:
ENTRY
PROC[info: LarkInfo]
RETURNS [continue:
BOOL, moreTones:
BOOL] =
TRUSTED {
ENABLE UNWIND=>NULL;
IF info.newActions#NIL AND ~flashWait THEN RETURN[TRUE, FALSE];
IF info.larkState=failed OR info.larkState=recovering THEN RETURN[FALSE, FALSE];
IF info.larkState=idle THEN { ringTune ← NIL; notes ← NIL; };
IF notes#NIL AND ~flashWait THEN RETURN[TRUE, TRUE];
IF waitTime=0 THEN waitTime
Process.SetTimeout[@info.stateChange, Process.MsecToTicks[waitTime]];
WAIT info.stateChange;
waitTime ← 0;
IF info.newActions#NIL THEN RETURN[TRUE, FALSE];
IF notes=NIL AND ringTune#NIL THEN notes←ringTune.notes;
RETURN[info.larkState#idle, notes#NIL];
};
IF ~(([,moreTones]←WaitQ[info]).continue) THEN EXIT;
IF moreTones THEN DoTones[];
};
EXITS Failed => {
P: ENTRY PROC[info: LarkInfo] = {IF info.larkState#recovering THEN info.larkStateiled;}; P[info]; EXIT; };
};
ENDLOOP;
info.larkProcess ← NIL;
};
Queue is a FIFO list of REFs, with a lastAction pointer to aid in rapid enqueuing.
QueueLarkAction:
INTERNAL
PROC[info: LarkInfo, ref:
REF] = {
elt: LIST OF REF = LIST[ref];
lst: LIST OF REF = info.lastAction;
Log.SLOG[100000B];
IF info.newActions=NIL THEN info.newActions ← elt ELSE IF lst=NIL THEN Thrush.pERROR ELSE lst.rest ← elt;
info.lastAction ← elt;
};
DequeueLarkAction:
INTERNAL
PROC[info: LarkInfo]
RETURNS [ref:
REF] =
INLINE {
elt: LIST OF REF ← info.newActions;
IF elt=NIL THEN RETURN[NIL];
ref𡤎lt.first;
info.newActions ← elt.rest;
};
LarkProblem:
PROC[remark:
ROPE, sInfo: SmartsInfo] = {
Log.ProblemFR[remark, $Lark, sInfo.larkInfo, TU.RefAddr[sInfo]];
};
QueueCommandSequence:
INTERNAL
PROC[
info: LarkInfo, commands: ROPE,
lState: LONG POINTER TO LState, scratchEv: Lark.CommandEvents]
RETURNS[echoAction: REF←NIL]= TRUSTED {
eventIndex: INTEGER←-1;
c: CHAR;
i: NAT;
index: INTEGER;
event: Lark.Event;
events: Lark.CommandEvents ← scratchEv;
nextState: LState ← [];
len: NAT;
echoAction ← echosOff[lState.echoStyle];
IF commands=NIL THEN RETURN; -- status quo
len ← commands.Length[];
FOR i
IN [0..len)
DO
SELECT (c𡤌ommands.Fetch[i]) FROM 'J, 'j => IF ~pd.backDoorOH THEN LOOP; ENDCASE;
SELECT c
FROM
'Z => { lState.xbar←ALL[0]; lState.lSw ← ALL[Lark.enabled]; event ← Lark.reset; };
'X, 'x => {
row: NAT← Digit[commands.Fetch[i+1]];
outputs: PACKED ARRAY [0..8) OF BOOLEAN ← LOOPHOLE[nextState.xbar[row]];
outputs[Digit[commands.Fetch[i+2]]] ← (c='X);
nextState.xbar[row] ← LOOPHOLE[outputs];
i←i+2;
LOOP;
};
'E, 'e => {
nextState.echoStyle ← commands.Fetch[i←i+1];
echoAction ← echosOn[nextState.echoStyle];
};
'M, 'm => {
nextState.voiceMode ←
SELECT commands.Fetch[i←i+1]
FROM
'0 => Lark.o3i1,
'1 => Lark.o2i2,
'2 => Lark.o1i1,
ENDCASE => ERROR;
};
ENDCASE=> {
IF c
IN ['a..'z]
THEN { event ← Lark.disabled; c𡤌-('a-'A); }
ELSE event ← Lark.enabled;
IF lStateForLetter[c]#none THEN nextState.lSw[lStateForLetter[c]] ← event;
};
ENDLOOP;
IF nextState=lState^ THEN RETURN [NIL];
IF nextState.echoStyle=lState.echoStyle OR ~pd.echoControl THEN echoAction←NIL;
FOR iteration:
NAT
IN [0..1]
DO
-- 0: compute size; 1: fill in result sequence.
index←-1;
IF nextState.voiceMode#lState.voiceMode
THEN
events[index←index+1] ← [voiceMode, nextState.voiceMode];
FOR i: LSwitches
DECREASING IN LSwitches
DO
IF nextState.lSw[i]#lState.lSw[i]
THEN
events[index←index+1] ← [lDevs[i], nextState.lSw[i]]; ENDLOOP;
FOR i:
NAT
IN [0..8)
DO
IF nextState.xbar[i]#lState.xbar[i]
THEN {
outputs: PACKED ARRAY[0..8) OF BOOLEAN = LOOPHOLE[lState.xbar[i]];
nxtOutputs: PACKED ARRAY[0..8) OF BOOLEAN = LOOPHOLE[nextState.xbar[i]];
FOR j:
NAT
IN [0..8)
DO
IF outputs[j]#nxtOutputs[j]
THEN
events[index←index+1] ← [
Lark.Device[LOOPHOLE[IF nxtOutputs[j] THEN 23 ELSE 22]],
LOOPHOLE[i*16+j] ];
ENDLOOP;
}; ENDLOOP;
IF index=-1 THEN { events←NIL; EXIT; };
IF iteration=0 THEN events ← NEW[Lark.CommandEventSequence[index+1]]; ENDLOOP;
QueueLarkAction[info, events];
lState^ ← nextState;
lState.lSw[xBarAll] ← Lark.disabled;
};
Digit: PROC[c: CHAR] RETURNS [digit: NAT] = INLINE { RETURN[c-'0]; };
RopeToDTMF:
PROC [r: Thrush.
ROPE]
RETURNS [ce: Lark.CommandEvents] = {
len: INT ← MIN[Lark.Passel.LAST, r.Length[]];
ce ← NEW[Lark.CommandEventSequence[len]];
FOR j:
INT
IN [0..ce.length)
DO
c: CHAR = r.Fetch[j];
ce.e[j] ← [touchPad,
SELECT c
FROM
IN ['0..'9] => LOOPHOLE[128 + c - '0],
IN ['a..'d] => LOOPHOLE[138 + c - 'a],
IN ['\001..'\037] => LOOPHOLE[LOOPHOLE[c,INTEGER]*10], -- 100 ms. pauses, 12-14 illegal!
'* => Lark.bStar,
'# => Lark.bThorp,
ENDCASE => Lark.bStar];
ENDLOOP;
};
PrepareRingTune:
INTERNAL
PROC[info: LarkInfo]
RETURNS[ringTune: ToneSpec] = {
ringTune ← NEW[ToneSpecRec←[oneRing: FALSE, volume: info.ringVolume, totalTime: 0, notes: NIL]];
IF info.ringDo
AND info.ringTuneRope#
NIL
THEN
TRUSTED {
totalTime: INTEGER𡤀
notes, lastNote: LIST OF Note;
note: Note ← [f1: 0, on: 0, off: 0, f2: 0, repetitions: 1];
inProgress: BOOL←FALSE;
PrepareTuneProc: PlayOps.BeepProc =
TRUSTED {
IF (beepFreq#0 AND beepFreq#note.f1)
OR ~inProgress
OR beepTime=0
THEN {
A note, end marker, or leading rest
IF inProgress
AND note.on#0
THEN {
-- in progress is previous note or leading rest.
noteEnt: LIST OF Note ← LIST[note];
IF lastNote=NIL THEN notes←lastNote←noteEnt
ELSE { lastNote.rest ← noteEnt; lastNote←noteEnt }; -- Append
note.off ← 0;
};
note.f1 ← beepFreq;
note.on ← beepTime;
inProgress ← TRUE;
}
ELSE IF beepFreq=0 THEN note.off ← note.off + beepTime
ELSE note.on ← note.on + beepTime;
Non-leading, non-trailing rest, or tied note.
totalTime ← totalTime+beepTime;
};
PlayOps.PlayString[music: info.ringTuneRope, beepProc: PrepareTuneProc];
PrepareTuneProc[0,0];
ringTune.notes ← notes;
ringTune.totalTime ← MAX[3000, totalTime];
}
ELSE ringTune.notes ←
(SELECT info.ringEnable FROM subdued, subduedTimed => subduedRingTone.notes, ENDCASE => ringTone.notes);
SELECT info.ringEnable
FROM
subdued, subduedTimed => {
ringTune.volume ← ringTune.volume + pd.subduedVolumeInterval;
ringTune.oneRing ← TRUE;
};
ENDCASE;
info.ringTune ← ringTune;
};
Deb:
PROC[info: LarkInfo, c:
CHAR, p1, p2, p3, p4:
IO.Value←[null[]]] = {
s: IO.STREAM;
IF ~ThNet.pd.debug THEN RETURN;
s←IO.ROS[];
s.PutF["<%g", char[c]];
SELECT c
FROM
'M => s.PutF["-- %g", p1];
'C => {
s.PutF[" -- [%b, %b]", p3, p4];
s.PutF[" %b(%d), %b(%d)", p1, p1, p2, p2];
};
ENDCASE;
s.PutRope[">\r"];
Log.Report[s.RopeFromROS[], $LarkDetailed, info];
};
QuickState:
ARRAY LarkState
OF
IO.Value = [
rope["none"], rope["idle"], rope["talking"], rope["trunkSignalling"],
rope["trunkTalking"], rope["trunkForwarding"], rope["trunkFlashing"], rope["failed"], rope["recovering"], rope["ringing"], rope["silence"],
rope["dialTone"], rope["ringBack"], rope["busyTone"], rope["errorTone"]];
toneStdCommand: ROPE = "SX01X14X06";
toneSpkrCommand: ROPE = "LSX03X14X06";
toneMonitorCommand: ROPE = "SX01X03X14X06";
silentSignalling: ROPE ← "HIX02X14";
noisySignalling: ROPE ← "HISTX02X10X21X26X14"; -- same as trunk talking (feedback problems?)
noisierSignalling: ROPE ← "HITLX02X30X23X26X24"; -- same as spkr trunk talking (feedback problems?)
trunkSignalling: ROPE ← silentSignalling;
Interpretation of the command string characters:
En-- echo mode; n IN [0..3); selects echoStyleStd (default), ...FD, ...BD, or ...Fwd
F -- T/R lead reversion
G -- A/A1 hookswitch control reversion
H -- Assert Telewall hookswitch
I -- Assert A/A1 to Telewall
J -- Assert Telewall hookswitch, maybe (depends on boolean variable)
L -- Lights led
R -- overrides volume control for ringing through speaker
S -- enables telset sidetone
T -- spMode; configures codecs for electronic trunk action
Xij -- connects crossbar input i to output j
Mn -- voiceMode; n IN [0..2); selects program O3I1 (default), O2I2, or O1I1
Z -- Resets hardware and crossbar
Crossbar Connections:
Port Input Output
0 dec1 co1
1 Xmtr Rcvr
2 from Telewall to Telewall
3 mike speaker
4 silence DTMF receiver
5 dec2 co2
6 line 1 out line 1 in
7 line 2 out line 2 in
larkCommands: ARRAY TerminalType OF ARRAY LarkState OF ROPE ← [
Telset
[
NIL,
-- none
"Z", -- idle
"SX01X06X10X14", -- talking
trunkSignalling, -- trunkSignalling
"HISTX02X10X21X26X14", -- trunkTalking, codec-assisted electronic mode
"E3HIX02X20X24", -- trunkForwarding, trunk to remote Lark connection. (need gain setting for echo?)
"Z", -- trunkFlashing, on-hook for a second.
"STX02X10X21X26X14", -- trunkFlashing, on-hook but otherwise unchanged.
"Z", -- failed
"Z", -- recovering
"RX03X06", -- ringing
"SX14", -- silence
toneStdCommand, toneStdCommand, toneStdCommand, toneStdCommand -- tones
],
Speakerphone
[
NIL,
-- none
"Z", -- idle
"E1LX03X06X30X14", -- talking
"HIX02X14X06", -- trunkSignalling
"E2M1THILX30X02X25X26X24X53", -- trunkTalking, gain-controlled digital mode
"E3HIX02X20X24", -- trunkForwarding; device stuff for this mode doesn't have much meaning.
"Z", -- trunkFlashing, on-hook for a second.
"TLX02X30X23X26X24", -- trunkFlashing
"Z", -- failed
"Z", -- recovering
"RX03X06", -- ringing
"LX14", -- silence
toneSpkrCommand, toneSpkrCommand, toneSpkrCommand, toneSpkrCommand -- tones
],
Monitoring Telset
[
NIL,
-- none
"Z", -- idle
"SX01X03X06X10X14", -- talking
"HIX02X14X06", -- trunkSignalling
"HISTLX02X10X21X23X14X26", -- trunkTalking, codec-assisted electronic mode
"E3HIX02X20X24", -- trunkForwarding, trunk to remote Lark connection. (meaning?)
"Z", -- trunkFlashing, on-hook for a second.
"STLX10X21X23X14X26", -- trunkFlashing
"Z", -- failed
"Z", -- recovering
"RX03X06", -- ringing
"SX14", -- silence
toneMonitorCommand, toneMonitorCommand, toneMonitorCommand, toneMonitorCommand -- tones
],
Radio Input, Telset/radio monitoring
[
NIL,
-- none
"Z", -- idle
"SX01X06X60X14", -- talking
"HIX02X14X06", -- trunkSignalling
"Z", -- trunkTalking
"E3HIX02X20X24", -- trunkForwarding, trunk to remote Lark connection. (meaning?)
"Z", -- trunkFlashing
"STLX10X21X23X14X26", -- trunkFlashing
"Z", -- failed
"Z", -- recovering
"RX03X06", -- ringing
"SX14", -- silence
toneStdCommand, toneStdCommand, toneStdCommand, toneStdCommand -- tones
]
];
echoStyleFD:
REF ←
NEW[Lark.EchoParameterRecord ←[
Front Door call using Speakerphone
buffer: out1,
buffer2Controlled: FALSE,
buffer1Controlled: TRUE,
decayTime: 5,
gain: [ 1024, 2048, 2048, 2048, 32767 ]
]];
echoStyleFwd: REF ← echoStyleFD;
echoStyleBD:
REF ←
NEW[Lark.EchoParameterRecord ←[
Back Door call using Speakerphone
buffer: in2,
buffer2Controlled: FALSE,
buffer1Controlled: TRUE,
decayTime: 10,
gain: [ 2048, 4096, 8192, 16384, 32767 ]
]];
echoStyleNoFD:
REF ←
NEW[Lark.EchoParameterRecord ←[
Standard FD or BD handset mode, no forwarding
buffer: out1, -- not interesting
buffer2Controlled: FALSE,
buffer1Controlled: FALSE,
decayTime: 0,
gain: [ 0, 0, 0, 0, 0 ]
]];
echoStyleNoFwd: REF ← echoStyleNoFD;
echoStyleNoBD:
REF ←
NEW[Lark.EchoParameterRecord ←[
Standard FD or BD handset mode, no forwarding
buffer: in2, -- not interesting
buffer2Controlled: FALSE,
buffer1Controlled: FALSE,
decayTime: 0,
gain: [ 0, 0, 0, 0, 0 ]
]];
echosOn: ARRAY CHAR['0..'3] OF REF←[ NIL, echoStyleFD, echoStyleBD, echoStyleFwd ];
echosOff:
ARRAY
CHAR ['0..'3]
OF
REF←[
NIL, echoStyleNoFD, echoStyleNoBD, echoStyleNoFwd ];
Nice.View[pd, "Lark Out PD"];
}.