Last Edited by: Teitelman, April 6, 1983 12:00 pm
DIRECTORY
Atom USING [Gensym, GetPName, PropList, GetPropFromList, PutPropOnList],
Convert USING [ValueToRope],
IO USING [EndOf, EndOfStream, GetRefAny, int, PutChar, PutF, PutRope, PutTV, RIS, rope, ROPE, SkipOver, STREAM, SyntaxError, TAB, WhiteSpace],
List USING [Append, DReverse, Memb, Nconc1, NthTail],
Rope USING [Cat, Concat, Equal, Fetch, Find, IsEmpty, Length, Replace, ROPE, Substr],
UserExec USING [CommandProc, ExecHandle, Expression, GetStreams, HistoryEvent, HistoryEventRecord, HistoryList, RegisterCommand, RegisterTransformation, RopeSubst, TransformProc],
TiogaOps USING [PutTextKey, GetTextKey, FirstChild, ViewerDoc, Ref, TextKeyNotFound],
UserExecExtras USING [],
UserExecPrivate USING [ExecPrivateRecord, ExpressionPrivateRecord, HistoryEventPrivateRecord, Zone, HistoryErrorCode]
;
HistoryImpl: CEDAR MONITOR LOCKS NARROW[exec.privateStuff, REF ExecPrivateRecord] USING exec: UserExec.ExecHandle
IMPORTS Atom, Convert, IO, List, Rope, UserExec, TiogaOps, UserExecPrivate
EXPORTS UserExec, UserExecExtras, UserExecPrivate
= BEGIN OPEN IO;
Types
HistoryEvent: TYPE = UserExec.HistoryEvent;
HistoryList: TYPE = UserExec.HistoryList;
EventAddress: TYPE = REF ANY;
REF INT => negative numbers count backwards, positive numbers refer to corresponding event number
ROPE => match any event containing indicated text.
ATOM => of form ^xyz, match event beginning with xyz, otherwise match event containing indicated text as identifier, i.e. neighboring characters not alphanumeric
connecting concrete and opaque types
ExecPrivateRecord: PUBLIC TYPE = UserExecPrivate.ExecPrivateRecord;
ExpressionPrivateRecord: PUBLIC TYPE = UserExecPrivate.ExpressionPrivateRecord;
HistoryEventPrivateRecord: PUBLIC TYPE = UserExecPrivate.HistoryEventPrivateRecord;
signals
HistoryError: PUBLIC ERROR [ec: UserExecPrivate.HistoryErrorCode, msg: Rope.ROPENIL] = CODE; -- raised by historyfind
GetInput: PROC [history: HistoryList, stream: IO.STREAM] RETURNS[ROPE] = {
input, input1: ROPENIL;
event: HistoryEvent;
eventAddress: EventAddress ← NIL;
DO
Add: PROC [r: ROPE] = {
IF input = NIL THEN input ← r
ELSE input ← Rope.Concat[Rope.Replace[base: input, start: Rope.Length[input] - 1, len: 1, with: "; "], r];
};
IO.SkipOver[stream, IO.WhiteSpace];
IF stream.EndOf[] THEN RETURN[input];
eventAddress ← IO.GetRefAny[stream ! IO.SyntaxError => IF Rope.Equal[msg, "Illegal character: ,"] THEN LOOP];
event ← HistoryFind[history: history, eventAddress: eventAddress];
IF Atom.GetPropFromList[propList: event.props, prop: $History] # NIL AND event.subEvents # NIL THEN
FOR l: LIST OF HistoryEvent ← event.subEvents, l.rest UNTIL l = NIL DO
Add[l.first.input];
ENDLOOP
ELSE Add[event.input];
ENDLOOP;
};
RedoCommand: UserExec.TransformProc = {
private: REF UserExecPrivate.ExecPrivateRecord = exec.privateStuff;
props: Atom.PropList = event.props;
history: HistoryList = private.historyList;
out: STREAM = UserExec.GetStreams[exec].out;
result ← GetInput[history, event.commandLineStream];
IF result = NIL THEN
{event: HistoryEvent = history.rest.first;
result ← event.input;
};
event.props ← Atom.PutPropOnList[event.props, $History, event.input];
};
CreateEvent: PUBLIC PROCEDURE [exec: UserExec.ExecHandle, input: ROPE] RETURNS [event: HistoryEvent] = {
event ← UserExecPrivate.Zone.NEW[UserExec.HistoryEventRecord ←
[
input: input,
privateStuff: UserExecPrivate.Zone.NEW[UserExecPrivate.HistoryEventPrivateRecord ←
[eventNum: 1]
]
]
];
IF exec = NIL THEN RETURN;
{node: TiogaOps.Ref = TiogaOps.FirstChild[TiogaOps.ViewerDoc[exec.viewer]]; -- assumes only one node in typescript.
private: REF ExecPrivateRecord = exec.privateStuff;
DoIt: ENTRY PROC [exec: UserExec.ExecHandle] = {
eventsPrivateStuff: REF UserExecPrivate.HistoryEventPrivateRecord = event.privateStuff;
eventsPrivateStuff.eventNum ← private.eventNum;
private.eventNum ← private.eventNum + 1;
private.historyList ← CONS[event, private.historyList];
TiogaOps.PutTextKey[node: node, where: TiogaOps.GetTextKey[node: node, key: exec ! TiogaOps.TextKeyNotFound => CONTINUE].where, key: event];
};
DoIt[exec];
};
}; -- of CreateEvent
CreateSubEvent: PUBLIC PROC [event: HistoryEvent, input: ROPE] RETURNS[subEvent: HistoryEvent] = {
creates a subevent, inheiriting the relevant properties from event, e.g. eventNum, and attaches it to event.
eventsPrivateStuff: REF UserExecPrivate.HistoryEventPrivateRecord = event.privateStuff;
subEvent ← UserExecPrivate.Zone.NEW[UserExec.HistoryEventRecord ←
[
input: input,
dontCorrect: event.dontCorrect,
privateStuff: UserExecPrivate.Zone.NEW[UserExecPrivate.HistoryEventPrivateRecord ←
[eventNum: eventsPrivateStuff.eventNum,
showInput: eventsPrivateStuff.showInput,
inCommandFile: eventsPrivateStuff.inCommandFile,
inCMFile: eventsPrivateStuff.inCMFile
]]
]
];
IF event.subEvents = NIL THEN event.subEvents ← LIST[subEvent]
ELSE TRUSTED {event.subEvents ← LOOPHOLE[List.Nconc1[LOOPHOLE[event.subEvents, LIST OF REF ANY], subEvent], LIST OF HistoryEvent]};
};
ShowHistory: UserExec.CommandProc = {
private: REF UserExecPrivate.ExecPrivateRecord ← exec.privateStuff;
concreteEvent: HistoryEvent = event;
props: Atom.PropList ← concreteEvent.props;
eventAddress: REF ANYNIL;
out: STREAM = UserExec.GetStreams[exec].out;
commandLineStream: STREAM = IO.RIS[concreteEvent.commandLine];
anything: BOOLFALSE;
concreteEvent.props ← Atom.PutPropOnList[concreteEvent.props, $History, concreteEvent.input];
concreteEvent.input ← "";
DO
IO.SkipOver[commandLineStream, IO.WhiteSpace];
IF commandLineStream.EndOf[] THEN EXIT;
eventAddress ← IO.GetRefAny[commandLineStream ! IO.EndOfStream => EXIT];
PrintHistory[eventAddress: eventAddress, history: private.historyList, handle: out];
anything ← TRUE;
ENDLOOP;
IF NOT anything THEN PrintHistory[eventAddress: NIL, history: private.historyList, handle: out]; -- history{cr} means everything
};
PrintHistory: PROCEDURE [eventAddress: EventAddress, history: UserExec.HistoryList, handle: STREAM] = {
PrintEvents[handle: handle,
events: IF eventAddress = NIL THEN history.rest ELSE LIST[HistoryFind[history, eventAddress]]];
};
PrintEvents: PROCEDURE [handle: STREAM, events: HistoryList] = {
PrintEvent1: PROC [event: HistoryEvent, indent: NAT] = {
eventsPrivateStuff: REF UserExecPrivate.HistoryEventPrivateRecord = event.privateStuff;
props: Atom.PropList ← event.props;
expr: UserExec.Expression = event.expression;
Indent: PROC = {FOR i: NAT IN [0..indent) DO handle.PutChar[TAB]; ENDLOOP};
PrintInput: PROC [input: ROPE] = {
Indent[];
handle.PutF["%g*n", rope[input]];
};
IF (historyCommand ← NARROW[Atom.GetPropFromList[props, $History]]) # NIL THEN
{Indent[]; handle.PutF["%g*n", rope[historyCommand]]};
PrintInput[event.input];
IF event.subEvents # NIL THEN
FOR lst: LIST OF HistoryEvent ← event.subEvents, lst.rest UNTIL lst = NIL DO
PrintEvent1[lst.first, indent + 1];
ENDLOOP
ELSE IF eventsPrivateStuff.state = completed AND expr = NIL THEN {
IF eventsPrivateStuff.value # NIL THEN handle.PutTV[eventsPrivateStuff.value]
}
ELSE {
Indent[];
SELECT eventsPrivateStuff.state FROM
causedAnError => handle.PutRope["{never finished - error}\n"];
notFinishedYet => handle.PutRope["{event not yet completed}\n"];
aborted => handle.PutRope["{aborted}\n"];
completed => {
privateExpr: REF ExpressionPrivateRecord = expr.privateStuff;
IF NOT Rope.IsEmpty[privateExpr.valueRope] THEN handle.PutF["= %g\n", rope[privateExpr.valueRope]];
};
ENDCASE => ERROR;
};
}; -- PrintEvent1
WHILE events # NIL DO
event: HistoryEvent = events.first;
eventsPrivateStuff: REF UserExecPrivate.HistoryEventPrivateRecord = event.privateStuff;
handle.PutF["%d.", int[eventsPrivateStuff.eventNum]];
PrintEvent1[event, 1];
events ← events.rest;
ENDLOOP;
}; -- of PrintEvents
procedures for directly manipulating the history list
HistoryFind: PROCEDURE [history: HistoryList, eventAddress: EventAddress, dontBackup: BOOLEANFALSE] RETURNS [event: HistoryEvent] = {
HistoryFindInt: PROC [n: INTEGER] = TRUSTED {
IF n < 0 THEN n ← -n - 1
ELSE
{event: HistoryEvent = history.first;
eventsPrivateStuff: REF UserExecPrivate.HistoryEventPrivateRecord = event.privateStuff;
n ← eventsPrivateStuff.eventNum - n;
};
IF n < 0 OR
(history ← LOOPHOLE[List.NthTail[LOOPHOLE[history, LIST OF REF ANY], n], HistoryList]) = NIL THEN
ERROR HistoryError[NotFound];
};
ref: REF ANY;
list: LIST OF EventAddress;
IF history = NIL THEN ERROR;
IF ~dontBackup THEN history ← history.rest; -- strips off this history command
IF eventAddress = NIL THEN NULL
ELSE WITH eventAddress SELECT FROM
l: LIST OF REF ANY => list ← l;
ENDCASE => list ← LIST[eventAddress];
WHILE list # NIL DO
IF history = NIL THEN GOTO NotFound;
WITH (ref ← list.first) SELECT FROM
x: REF INT => HistoryFindInt[x^];
x: REF INTEGER => HistoryFindInt[x^];
ENDCASE =>
UNTIL history = NIL DO
IF EventMatch[history.first, ref] THEN EXIT;
history ← history.rest;
REPEAT
FINISHED => GOTO NotFound;
ENDLOOP;
list ← list.rest;
ENDLOOP;
RETURN[history.first];
EXITS
NotFound => ERROR HistoryError[NotFound];
}; -- of HistoryFind
EventMatch: PROCEDURE [event: HistoryEvent, key: REF ANY] RETURNS [BOOLEAN] = {
IF Atom.GetPropFromList[propList: event.props, prop: $History] # NIL AND event.subEvents # NIL THEN RETURN[EventMatch[event.subEvents.first, key]];
WITH key SELECT FROM
r: ROPE => RETURN[(Rope.Find[s1: event.input, s2: r, case: FALSE] # -1)];
a: ATOM =>
{
r: ROPE ← Atom.GetPName[a];
IF Rope.Fetch[r, 0] = '^ THEN -- match only at start of event.
RETURN[Rope.Find[s1: event.input, s2: Rope.Substr[base: r, start: 1]] = 0]
ELSE IF Rope.Fetch[r, 0] = '< AND Rope.Fetch[r, Rope.Length[r] - 1] = '> THEN -- match as id, i.e. neighboring characters cannot be alphanumeric.
{
i: INT ← 0;
eventLength: INT = Rope.Length[event.input];
rLen: INT ← Rope.Length[r];
IsSepr: PROC [pos: INT] RETURNS[BOOLEAN] = {
RETURN[pos >= eventLength OR pos < 0 OR
(SELECT Rope.Fetch[event.input, pos] FROM
IN ['A..'Z], IN ['a..'z], IN ['0..'9] => FALSE,
ENDCASE => TRUE)
]
};
r ← Rope.Substr[base: r, start: 1, len: rLen - 2]; -- strip off <>
rLen ← rLen - 2;
WHILE (i ← Rope.Find[s1: event.input, s2: r, pos1: i, case: FALSE]) # -1
DO
IF IsSepr[i - 1] AND IsSepr[i + rLen] THEN RETURN[TRUE];
i ← i + 1;
REPEAT
FINISHED => RETURN[FALSE];
ENDLOOP;
}
ELSE RETURN[(Rope.Find[s1: event.input, s2: r, case: FALSE] # -1)];
};
ENDCASE => RETURN[FALSE];
}; -- of EventMatch
SynonymList: TYPE = LIST OF REF SynonymRecord;
SynonymRecord: TYPE = RECORD[key, val: ROPE];
UseCommand: UserExec.TransformProc = {
private: REF UserExecPrivate.ExecPrivateRecord = exec.privateStuff;
history: HistoryList = private.historyList;
out: STREAM = UserExec.GetStreams[exec].out;
stream: STREAM = event.commandLineStream;
props: Atom.PropList = event.props;
new, old: LIST OF LIST OF REF ANYNIL;
eventSpec, previouslySeen: LIST OF REF ANYNIL;
oldInput: ROPE;
tem, lst: LIST OF REF ANYNIL; -- temporaries
UseRecord: TYPE = RECORD[args: LIST OF LIST OF REF ANY, oldInput: ROPE];
synonyms: SynonymList;
state: {New, Old} ← New;
IntMemb: PROC [i: INT, lst: LIST OF REF ANY] RETURNS[BOOLEAN] = {
FOR l: LIST OF REF ANY ← lst, l.rest UNTIL l = NIL DO
WITH l.first SELECT FROM
r: REF INT => IF r^ = i THEN RETURN[TRUE];
ENDCASE;
ENDLOOP;
RETURN[FALSE]
};
RopeMemb: PROC [rope: ROPE, lst: LIST OF REF ANY] RETURNS[BOOLEAN] = {
FOR l: LIST OF REF ANY ← lst, l.rest UNTIL l = NIL DO
WITH l.first SELECT FROM
r: ROPE => IF Rope.Equal[rope, r] THEN RETURN[TRUE];
ENDCASE;
ENDLOOP;
RETURN[FALSE]
};
RealMemb: PROC [r: REAL, lst: LIST OF REF ANY] RETURNS[BOOLEAN] = {
FOR l: LIST OF REF ANY ← lst, l.rest UNTIL l = NIL DO
WITH l.first SELECT FROM
ref: REF REAL => IF ABS[ref^ - r] < .00001 THEN RETURN[TRUE];
ENDCASE;
ENDLOOP;
RETURN[FALSE]
};
IO.SkipOver[stream, IO.WhiteSpace];
IF stream.EndOf[] THEN ERROR HistoryError[UseWhat];
parses command line using simple finite state machine
DO
x: REF ANY ← IO.GetRefAny[stream ! IO.EndOfStream =>
{
SELECT state FROM
New => new ← CONS[lst, new];
Old => old ← CONS[lst, old];
ENDCASE => ERROR;
EXIT;
};
];
IF lst # NIL THEN -- IN, AND, FOR not interpreted as separators when they appear first, last, or immediately following another operator, e.g. USE IN FOR IN AND AND FOR FOR will work
WITH x SELECT FROM
a: ATOM => SELECT TRUE FROM
Rope.Equal["FOR", Atom.GetPName[a], FALSE] =>
IF state = New THEN
{
new ← CONS[lst, new]; -- should go on end. would really like to use Nconc1 but then would have to loophole.
previouslySeen ← List.Append[lst, previouslySeen]; -- lis of all new items seen
state ← Old;
lst ← NIL;
LOOP
};
Rope.Equal["AND", Atom.GetPName[a], FALSE] =>
{
IF state = Old THEN old ← CONS[lst, old]
ELSE IF state = New THEN new ← CONS[lst, new]; -- e.g. user types USE A AND B following previous USE command, i.e. no old
state ← New;
lst ← NIL;
LOOP;
};
Rope.Equal["IN", Atom.GetPName[a], FALSE] =>
{
IF state = New AND new = NIL THEN new ← CONS[lst, new]
ELSE IF state = Old THEN old ← CONS[lst, old];
oldInput ← GetInput[history, stream];
EXIT;
};
ENDCASE;
ENDCASE; -- not an atom
lst ← List.Nconc1[lst, x];
{
seen: BOOLEAN;
rope: ROPE;
WITH x SELECT FROM
a: ATOM => IF seen ← List.Memb[a, previouslySeen] THEN rope ← Atom.GetPName[a];
r: REF INT => IF seen ← IntMemb[r^, previouslySeen] THEN rope ← Convert.ValueToRope[[signed[r^]]];
r: REF REAL => IF seen ← RealMemb[r^, previouslySeen] THEN rope ← Convert.ValueToRope[[real[r^]]];
r: ROPE => IF seen ← RopeMemb[r, previouslySeen] THEN rope ← r;
ENDCASE => seen ← FALSE;
IF seen THEN synonyms ← CONS[NEW[SynonymRecord ← [rope, Atom.GetPName[Atom.Gensym[]]]], synonyms]; -- enables USE A B FOR B A, USE A FOR B AND B FOR A, or USE A FOR B AND B C FOR A
*** WHAT ABOUT USE "X" FOR "Y" AND "Y" FOR "X"??
};
ENDLOOP;
IF old # NIL THEN
the arguments were explicitly named by user, e.g. USE ... FOR ...
{useArgs ← CONS[old, oldInput]; to be saved on history list in case user gives a user command referring to this event
IF oldInput = NIL THEN
{IF old # NIL THEN -- In case of USE FOO FOR FIE, i.e. no IN, searches for FIE.
oldInput ← GetInput[history, IO.RIS[MakeRope[old.first.first], stream]]
ELSE -- e.g. compile mumble, followed by use bind.
{
oldInput ← HistoryFind[history: history, eventAddress: NIL].input;
old ← LIST[LIST[IO.GetRefAny[IO.RIS[rope: oldInput]]]];
};
};
event.props ← Atom.PutPropOnList[event.props, $UseRecord, NEW[UseRecord ← [args: old, oldInput: oldInput]]];
ELSE IF useArgs # NIL THEN arguments specified by other USE command
{old ← NARROW[useArgs.first, LIST OF REF ANY];
expr ← Cdr[useArgs];
IF old.rest # NIL AND new.rest = NIL THEN user types command of the form USE A FOR B AND C FOR D and follows this with USE E F
FOR l: LIST OF LIST OF REF ANY ← old, l.rest UNTIL l = NIL DO l.first ← LIST[l.first]; ENDLOOP}
ELSE IF new.rest # NIL more than one operation but no new, e.g. USE FOO IN A AND B, or else multiple arguments specified in the referent operation, e.g. it was of the form USE A FOR B AND C FOR D
THEN ERROR HistoryError[UseForWhat]
here should be a check for multiple event
TRUSTED
{old ← LOOPHOLE[List.DReverse[LOOPHOLE[old]]] ;-- must get order right or trick with synonyms won't work, because will have already substituted for it.
new ← LOOPHOLE[List.DReverse[LOOPHOLE[new]]];
};
result ← UseCommandImpl[old, new, oldInput, synonyms];
event.props ← Atom.PutPropOnList[event.props, $History, event.input];
}; -- of UseCommand
MakeRope: PROC [ref: REF ANY] RETURNS[ROPE] = {
WITH ref SELECT FROM
a: ATOM => RETURN[Atom.GetPName[a]];
r: REF INT => RETURN[Convert.ValueToRope[[signed[r^]]]];
r: REF REAL => RETURN[Convert.ValueToRope[[real[r^]]]];
r: ROPE => RETURN[r];
r: REF BOOLEAN => IF r^ THEN RETURN["TRUE"] ELSE RETURN["FALSE"];
ENDCASE => RETURN[""];
};
UseCommandImpl: PROC [oldList, newList: LIST OF LIST OF REF ANY, oldInput: ROPE, synonyms: SynonymList] RETURNS[newInput: ROPE] = {
success: BOOLFALSE;
UseImpl1: PROC [old, new: LIST OF REF ANY, oldInput: ROPE] RETURNS[ROPE] = {
old0: LIST OF REF ANY ← old;
new0: LIST OF REF ANY ← new;
tem: ROPE;
oldflg, newflg: BOOLEANFALSE;
val: ROPENIL;
r, r1: ROPE;
AppendRope: PROC = {
IF val = NIL THEN val ← r ELSE val ← Rope.Cat[Rope.Substr[base: val, len: Rope.Length[val] - 1], "; ", r];
};
r ← oldInput;
DO -- whole body is one big iteration
tem ← MakeRope[new0.first];
see if tem is on synonyms
FOR s: SynonymList ← synonyms, s.rest UNTIL s = NIL DO
IF Rope.Equal[s.first.key, tem] THEN tem ← s.first.val;
ENDLOOP;
r1 ← UserExec.RopeSubst[base: r, new: tem, old: MakeRope[old0.first]];
IF r # r1 THEN success ← TRUE;
r ← r1;
IF (new0 ← new0.rest) = NIL THEN newflg ← TRUE;
IF (old0 ← old0.rest) = NIL THEN oldflg ← TRUE;
IF new0 # NIL AND old0 # NIL THEN LOOP;
IF (exprs0 ← exprs0.rest) = NIL THEN
{IF old0 = NIL AND new0 = NIL THEN GOTO Out;
exprsflg ← TRUE;
AppendRope[];
r ← oldInput;
};
IF exprsflg AND newflg AND oldflg THEN ERROR HistoryError[UseHuh];
IF new0 = NIL THEN new0 ← new;
IF old0 = NIL THEN old0 ← old;
REPEAT
Out => {AppendRope[]; RETURN[val]};
ENDLOOP;
}; -- of UseImpl1
main body of UseCommandImplUseImpl
newInput ← oldInput;
UNTIL newList = NIL DO
newInput ← UseImpl1[oldList.first, newList.first, newInput];
oldList ← oldList.rest;
newList ← newList.rest;
ENDLOOP;
IF oldList # NIL THEN ERROR HistoryError[UseWhat];
IF ~success THEN ERROR HistoryError[NotFound];
FOR l: SynonymList ← synonyms, l.rest UNTIL l = NIL DO
newInput ← UserExec.RopeSubst[new: NARROW[synonyms.first.key], old: NARROW[synonyms.first.val], base: newInput];
ENDLOOP;
}; -- of UseCommandImpl
Initialization
UserExec.RegisterTransformation["Redo", RedoCommand, "replays the indicated event(s).","replays the indicated event(s), e.g. redo comp bind. Events can be indicated by (a) their event number, a positive integer; (b) relative event number, a negative integer which indicates how many events before the present, e.g. redo -1 is the last event; or (c) a pattern that matches with the input of the event, without regard for case. A sequence of characters will match anywhere in the event, an expression of the form <id> will only match with id where its neighbors are not alphanumeric."];
UserExec.RegisterCommand["History", ShowHistory, "Shows History.", "Shows History. History{cr} shows entire history list. History {eventNum} just the corresponding event, e.g. History -1"];
UserExec.RegisterTransformation["Use", UseCommand, "substitutes new text for old text in the indicated event(s)", "Form is Use New For Old In eventSpec. e.g. Use mesa For bcd IN -1. Substitution is always on a character basis.If eventSpec specifies more than one event, a compound event will be constructed. If there are more new arguments than old arguments, the substitution is distributed, e.g. Use 1 2 3 For 0 IN -1 -2 will construct an event consisting of the concatenation of the last two events, and then execute that event first with 1 substituted for 0, then 2 for 0 then 3 for 0. If the eventSpec is omitted, the first event that contains the first old argument is used, e.g. Use mesa For bcd will search for first event containing 'bcd' and substitute in that. If no old argument specified, and the event was itself the result of a use command, substitute for the original old arguments, e.g. use a for b, followed by use c d e is equivalent to use c d e for b. Finally, if no new arguments are specified, old is first token, e.g. compile mumble, followed by use bind."];
END. -- of HistoryImpl
change before fixed redo redo loop
GetInput
: PROC [history: HistoryList, stream: IO.STREAM] RETURNS[ROPE] = {
input: ROPENIL;
event: HistoryEvent;
eventAddress: EventAddress ← NIL;
DO
IO.SkipOver[stream, IO.WhiteSpace];
IF stream.EndOf[] THEN RETURN[input];
eventAddress ← IO.GetRefAny[stream];
event ← HistoryFind[history: history, eventAddress: eventAddress];
IF input = NIL THEN input ← event.input
ELSE input ← Rope.Concat[Rope.Replace[base: input, start: Rope.Length[input] - 1, len: 1, with: "; "], event.input];
ENDLOOP;
};