-- TEditInputOpsImpl.mesa; Edited by Paxton on February 8, 1983 9:34 am
-- Edited by McGregor on July 30, 1982 3:15 pm
Last Edited by: Maxwell, January 14, 1983 1:58 pm
DIRECTORY
EditSpan
USING [ChangeLooks, ChangeNesting, CannotDoEdit, Copy, Delete, InsertTextNode,
Merge, Move, MoveOnto, Place, Replace, SaveForPaste, SavedForPaste, Split, Transpose],
EditSpanSupport USING [Apply],
MessageWindow USING [Append, Blink],
Rope USING [ROPE, Substr, Concat],
RopeEdit USING [AlphaNumericChar],
TextEdit USING [DeleteText, FetchChar, FetchLooks, FromRope, Offset, Ref, RefTextNode, Size],
TextLooks USING [Look, Looks, allLooks, noLooks],
TextLooksSupport USING [ModifyLooks],
TextNode USING [Backward, FirstChild, LastLocWithin, Level, Location, MakeNodeLoc, MakeNodeSpan, NarrowToTextNode, NodeItself, nullSpan, Offset, Parent, pZone, Ref, RefTextNode, Root, Span, StepForward, StepBackward],
TEditDisplay USING [EstablishLine],
TEditDocument USING [BeforeAfter, Selection, SelectionId, SelectionGrain, SelectionPoint, SelectionRec, TEditDocumentData],
TEditImpl USING [CaretAtEnd],
TEditInput USING [currentEvent],
TEditInputOps,
TEditLocks USING [Access, Lock, LockBoth, LockRef, Unlock],
TEditOps,
TEditProfile USING [editTypeScripts],
TEditRefresh USING [ScrollToEndOfSel],
TEditSelection USING [Alloc, CaretVisible, Copy, Free, Deselect, GetSelectionGrain, InsertionPoint, LockBothSelections, LockSel, MakeSelection, MakePointSelection, nilSel, oldSel, pSel, SelectionRoot, sSel, UnlockBothSelections, UnlockDocAndPSel, UnlockSel],
TypeScript USING [ChangeLooks],
ViewerClasses USING [Viewer];
TEditInputOpsImpl: CEDAR PROGRAM
IMPORTS EditSpan, MessageWindow, EditSpanSupport, Rope, RopeEdit, TextEdit, TextLooksSupport, TextNode, TEditDisplay, TEditImpl, TEditInput, TEditInputOps, TEditLocks, TEditProfile, TEditRefresh, TEditSelection, TypeScript
EXPORTS TEditInputOps, TEditOps = BEGIN OPEN TEditDocument, TEditSelection;
pdelNode: TextNode.RefTextNode = TextEdit.FromRope["!"];
DoPendingDelete:
PUBLIC
PROC = {
like a replace of pSel by a single character, then delete that character.
same as calling Delete for pSel a text selection, but NOT for pSel a node/branch selection.
PendingDelete:
PROC [root: TextEdit.Ref, tSel: Selection] = {
pSel.pendingDelete ← TRUE;
tSel^ ← nilSel^;
tSel.granularity ← char;
tSel.looks ← pSel.looks;
tSel.start.pos ← tSel.end.pos ← [pdelNode,0];
tSel.pendingDelete ← FALSE;
CopyToDoc[targetSel: pSel, srcSel: tSel, target: primary, lock: FALSE];
Delete[saveForPaste: FALSE] };
CallWithLocks[PendingDelete] };
NodeSel:
PROC [sel: Selection]
RETURNS [
BOOLEAN] =
INLINE {
RETURN [GetSelectionGrain[sel]=node OR sel.start.pos.node # sel.end.pos.node] };
Delete:
PUBLIC
PROC [saveForPaste:
BOOLEAN ←
TRUE] = {
DoDelete:
PROC [root: TextEdit.Ref, tSel: Selection] = {
Deselect[];
tSel.pendingDelete ← FALSE;
SELECT GetSelectionGrain[tSel]
FROM
point => NULL;
node =>
BEGIN
-- this is complex because must worry about deleting all of the document
newSelNode: TextNode.Ref ← TextNode.StepForward[tSel.end.pos.node];
newSelText: TextNode.RefTextNode ← TextNode.NarrowToTextNode[newSelNode];
newSelInsertion: BeforeAfter;
IF newSelNode=
NIL
THEN {
-- deleting the last node of the doc
newSelNode ← TextNode.StepBackward[tSel.start.pos.node];
IF newSelNode=
NIL
OR newSelNode=root
THEN {
-- deleting all the nodes
child: TextEdit.Ref ← TextNode.FirstChild[root];
tSel.start.pos.node ← child;
newSelNode ← EditSpan.InsertTextNode[root, child,
before, FALSE, TEditInput.currentEvent] };
newSelText ← TextNode.NarrowToTextNode[newSelNode];
newSelInsertion ← IF newSelText#NIL AND TextEdit.Size[newSelText] > 0 THEN after ELSE before }
ELSE { newSelInsertion ← before };
EditSpan.Delete[
SelectionRoot[tSel],
TextNode.MakeNodeSpan[tSel.start.pos.node,tSel.end.pos.node],
TEditInput.currentEvent,saveForPaste ! EditSpan.CannotDoEdit => GOTO Bad];
IF newSelText #
NIL
THEN {
tSel.start.pos.node ← tSel.end.pos.node ← newSelText;
tSel.start.pos.where ← tSel.end.pos.where ←
IF newSelInsertion=before THEN 0
ELSE TextEdit.Size[newSelText] -- -1? --;
tSel.granularity ← point }
ELSE {
-- the new selection node is not a text node
tSel.start.pos ← tSel.end.pos ← TextNode.MakeNodeLoc[newSelNode];
tSel.granularity ← node };
tSel.insertion ← newSelInsertion;
END;
ENDCASE =>
BEGIN
EditSpan.Delete[
SelectionRoot[tSel],
[tSel.start.pos, tSel.end.pos],
TEditInput.currentEvent,saveForPaste !
EditSpan.CannotDoEdit => GOTO Bad];
tSel.end.pos ← tSel.start.pos;
tSel.granularity ← point;
tSel.insertion ← before;
END;
MakeSelection[selection: primary, new: tSel];
EXITS Bad => { MakeSelection[selection: primary, new: tSel]; EditFailed[] }};
CallWithLocks[DoDelete] };
EditFailed:
PUBLIC
PROC [msg: Rope.
ROPE ←
NIL] = {
OPEN MessageWindow;
Append[IF msg=NIL THEN "Can't do it." ELSE msg, TRUE]; Blink[] };
CaretLoc:
PUBLIC
PROC [s: Selection ←
NIL]
RETURNS [TextNode.Location] = {
IF s=NIL THEN s ← pSel;
IF GetSelectionGrain[s] = node
THEN
RETURN [
[IF s.insertion = before THEN s.start.pos.node ELSE s.end.pos.node, TextNode.NodeItself]];
IF s.insertion = before THEN RETURN [s.start.pos];
RETURN [[s.end.pos.node, s.end.pos.where+1]] };
CallWithLocks:
PUBLIC
PROC
[proc: PROC [root: TextEdit.Ref, tSel: Selection], access: TEditLocks.Access ← write] = BEGIN
root: TextEdit.Ref;
tSel: Selection;
lockRef: TEditLocks.LockRef;
BEGIN
ENABLE
UNWIND => {
UnlockSel[primary];
IF lockRef # NIL THEN TEditLocks.Unlock[root];
IF tSel # NIL THEN Free[tSel] };
LockSel[primary, "CallWithLocks"];
IF (access=write
AND ~CheckReadonly[pSel])
OR (root ← SelectionRoot[pSel])=
NIL
THEN {
UnlockSel[primary]; RETURN };
lockRef ← TEditLocks.Lock[root, "CallWithLocks", access];
tSel ← Alloc[];
TEditSelection.Copy[source: pSel, dest: tSel];
proc[root, tSel];
Free[tSel]; tSel ← NIL;
UnlockDocAndPSel[root];
END END;
BackSpace:
PUBLIC
PROC [count:
INT ← 1] = {
DoBackSpace:
PROC [root: TextEdit.Ref, tSel: Selection] = {
node: TextNode.RefTextNode;
flush: TextNode.Location ← InsertionPoint[tSel];
IF flush.where=TextNode.NodeItself THEN GOTO Bad;
IF (node ← TextNode.NarrowToTextNode[flush.node])=NIL THEN GOTO Bad;
IF flush.where=0 THEN { Join[]; RETURN }; -- already at start of node; do a Join
IF (count ← MIN[count,flush.where]) <= 0 THEN GOTO Bad;
Deselect[primary];
flush.where ← flush.where-count;
TextEdit.DeleteText[root, node, flush.where, count, TEditInput.currentEvent];
MakePointSelection[tSel, flush];
EXITS Bad => EditFailed[] };
IF count > 0 THEN CallWithLocks[DoBackSpace];
};
FindPrevWord:
PUBLIC
PROC [node: TextNode.RefTextNode, offset: TextNode.Offset]
RETURNS [nChars: CARDINAL] = {
nChars ← 0;
WHILE offset>0
AND ~RopeEdit.AlphaNumericChar[TextEdit.FetchChar[node, offset-1]]
DO
offset ← offset - 1; nChars ← nChars + 1; ENDLOOP;
WHILE offset>0
AND RopeEdit.AlphaNumericChar[TextEdit.FetchChar[node, offset-1]]
DO
offset ← offset - 1; nChars ← nChars + 1; ENDLOOP;
};
BackWord:
PUBLIC
PROC [count:
INT ← 1] =
BEGIN
DoBackWord:
PROC [root: TextEdit.Ref, tSel: Selection] = {
node: TextNode.RefTextNode;
nChars: CARDINAL ← 0;
pos: TextNode.Location ← InsertionPoint[tSel];
IF (node ← TextNode.NarrowToTextNode[pos.node])=NIL THEN GOTO Bad;
IF pos.where = TextNode.NodeItself THEN GOTO Bad;
Deselect[primary];
FOR garbage:
INT
IN [0..count)
DO
wChars: CARDINAL ← FindPrevWord[node,pos.where];
pos.where ← pos.where - wChars;
nChars ← nChars + wChars;
ENDLOOP;
TextEdit.DeleteText[root, node, pos.where, nChars, TEditInput.currentEvent];
MakePointSelection[tSel, pos];
EXITS Bad => EditFailed[] };
IF count > 0 THEN CallWithLocks[DoBackWord];
END;
GoToPreviousWord:
PUBLIC
PROC [count:
INT ← 1] =
BEGIN
DoGoToPreviousWord:
PROC [root: TextEdit.Ref, tSel: Selection] = {
pos: TextNode.Location;
node: TextNode.RefTextNode;
nChars: CARDINAL;
pos ← InsertionPoint[tSel];
FOR garbage:
INT
IN [0..count)
DO
IF (node ← TextNode.NarrowToTextNode[pos.node])=
NIL
OR
pos.where=TextNode.NodeItself
OR pos.where=0
THEN {
TEditInputOps.GoToPreviousNode; RETURN };
nChars ← FindPrevWord[node,pos.where];
pos.where ← pos.where - nChars;
ENDLOOP;
MakePointSelection[tSel,pos] };
IF count > 0 THEN CallWithLocks[DoGoToPreviousWord, read];
END;
CopyToTypeScript:
PROC [targetSel: Selection, source: TextNode.Span] = {
TSCopy:
PROC [node: TextNode.RefTextNode, start, len: TextNode.Offset]
RETURNS [stop: BOOLEAN] = {
rope: Rope.ROPE ← Rope.Substr[node.rope, start, len];
IF node # source.end.node THEN rope ← Rope.Concat[rope, "\n"]; -- add CR's between nodes
-- shove it in as though typed...
targetSel.viewer.class.notify[targetSel.viewer, TextNode.pZone.LIST[rope]];
RETURN [FALSE] };
EditSpanSupport.Apply[source,TSCopy] };
ConvertNodeSelects:
PROC [sel: Selection]
RETURNS [
BOOLEAN] = {
IF GetSelectionGrain[sel] # node THEN RETURN [FALSE];
sel.start.pos.where ← sel.end.pos.where ← TextNode.NodeItself;
RETURN [TRUE] };
ExpandToNodeSelection:
PROC [sel: Selection] = {
sel.start.pos.where ← 0;
sel.end.pos.where ←
MAX[TextEdit.Size[TextNode.NarrowToTextNode[sel.end.pos.node]],1]-1;
sel.granularity ← node;
};
UnConvertNodeSelects:
PROC [sel: Selection] = {
IF GetSelectionGrain[sel] # node THEN RETURN;
sel.start.pos.where ← 0;
sel.end.pos.where ← MAX[TextEdit.Size[TextNode.NarrowToTextNode[sel.end.pos.node]]-1,0] };
CallWithBothLocked:
PUBLIC
PROC [
proc: PROC [sourceRoot, destRoot: TextEdit.Ref, tSel, srcSel, targetSel: Selection],
targetSel, srcSel: Selection, sourceAccess: TEditLocks.Access] = BEGIN
sourceRoot, destRoot: TextEdit.Ref;
tSel, tSel1, tSel2: Selection;
lockRef: TEditLocks.LockRef;
Cleanup:
PROC = {
IF lockRef # NIL THEN { TEditLocks.Unlock[sourceRoot]; TEditLocks.Unlock[destRoot] };
IF tSel # NIL THEN Free[tSel];
IF tSel1 # NIL THEN Free[tSel1];
IF tSel2 # NIL THEN Free[tSel2];
UnlockBothSelections[] };
BEGIN
ENABLE UNWIND => { Cleanup[] };
LockBothSelections["CallWithBothLocked"];
IF srcSel.viewer=NIL OR targetSel.viewer=NIL THEN { UnlockBothSelections[]; RETURN };
IF ~CheckReadonly[targetSel]
OR
-- don't edit a readonly document
(sourceAccess=write
AND ~CheckReadonly[srcSel]
) THEN {
Deselect[selection: secondary]; UnlockBothSelections[]; RETURN };
tSel1 ← Alloc[]; tSel2 ← Alloc[]; tSel ← Alloc[];
TEditSelection.Copy[source: srcSel, dest: tSel1];
TEditSelection.Copy[source: targetSel, dest: tSel2];
TEditSelection.Copy[source: targetSel, dest: tSel];
sourceRoot ← SelectionRoot[srcSel];
destRoot ← SelectionRoot[targetSel];
[lockRef, ----] ← TEditLocks.LockBoth[
sourceRoot, destRoot, "CallWithBothLocked", sourceAccess, write];
Deselect[selection: secondary];
Deselect[selection: primary];
proc[sourceRoot, destRoot, tSel, tSel1, tSel2];
Cleanup[];
END END;
CopyToDoc:
PROC [targetSel, srcSel: Selection, target: SelectionId, lock:
BOOL ←
TRUE] = {
DoCopyToDoc:
PROC [sourceRoot, destRoot: TextEdit.Ref, tSel, srcSel, targetSel: Selection] = {
wordMode: BOOLEAN = FALSE; -- (srcSel.granularity = word);
nodeCopy: BOOLEAN ← ConvertNodeSelects[srcSel];
pDel: BOOLEAN ← tSel.pendingDelete;
IF pDel
THEN {
-- replace target by source
[] ← ConvertNodeSelects[tSel];
[[tSel.start.pos, tSel.end.pos]] ←
EditSpan.Replace[destRoot, sourceRoot,
[tSel.start.pos, tSel.end.pos],
[srcSel.start.pos, srcSel.end.pos], wordMode, TRUE,
TEditInput.currentEvent ! EditSpan.CannotDoEdit => GOTO Bad];
tSel.pendingDelete ← FALSE }
ELSE {
-- source goes to target caret
loc: TextNode.Location ← InsertionPoint[tSel];
unnest: INTEGER ← 0; -- amount to unnest by if copying nodes after
where: EditSpan.Place ← IF tSel.insertion = before THEN before ELSE after;
IF nodeCopy
THEN {
-- don't copy nodes into target node
IF where = before
AND loc.where > 0
AND
loc.where = TextEdit.Size[TextNode.NarrowToTextNode[loc.node]]
THEN
where ← after; -- caret at end of node, so copy after
loc.where ← TextNode.NodeItself };
IF nodeCopy
AND where=after
AND tSel.start.pos.node#tSel.end.pos.node
THEN
unnest ← TextNode.Level[tSel.end.pos.node]-TextNode.Level[tSel.start.pos.node];
[[tSel.start.pos, tSel.end.pos]] ←
EditSpan.Copy[destRoot, sourceRoot, loc,
[srcSel.start.pos, srcSel.end.pos], wordMode, where, 0,
TEditInput.currentEvent ! EditSpan.CannotDoEdit => GOTO Bad];
IF unnest > 0
THEN
-- unnest so that copied span starts at same level as start of dest span
[[tSel.start.pos, tSel.end.pos]] ←
EditSpan.ChangeNesting[root: destRoot, span: [tSel.start.pos, tSel.end.pos],
change: -unnest, event: TEditInput.currentEvent !
EditSpan.CannotDoEdit => CONTINUE];
};
tSel.granularity ← srcSel.granularity;
UnConvertNodeSelects[tSel];
tSel.insertion ← after;
MakeSelection[selection: primary, new: tSel];
TEditSelection.Copy[source: tSel, dest: oldSel]; -- save the copied selection for Repeat's
EXITS Bad => {
MakeSelection[selection: primary, new: IF target=primary THEN targetSel ELSE srcSel];
EditFailed[] }};
IF lock THEN CallWithBothLocked[DoCopyToDoc, targetSel, srcSel, read]
ELSE {
-- special hack for DoPendingDelete.
tSel: Selection ← Alloc[];
TEditSelection.Copy[source: targetSel, dest: tSel];
DoCopyToDoc[SelectionRoot[srcSel], SelectionRoot[targetSel], tSel, srcSel, targetSel];
Free[tSel] }};
Copy:
PUBLIC
PROCEDURE [target: SelectionId ← primary] =
BEGIN
ENABLE UNWIND => UnlockBothSelections[];
targetSel: Selection ← IF target=primary THEN pSel ELSE sSel;
srcSel: Selection ← IF target=primary THEN sSel ELSE pSel;
LockBothSelections["Copy"];
IF srcSel.viewer#NIL AND targetSel.viewer#NIL THEN DoCopy[target, targetSel, srcSel];
UnlockBothSelections[];
END;
CheckReadonly:
PUBLIC
PROC [targetSel: Selection]
RETURNS [
BOOL] = {
IF targetSel.viewer=NIL OR ~targetSel.data.readOnly THEN RETURN [TRUE];
EditFailed["Cannot modify read only document."];
RETURN [FALSE] };
DoCopy:
PROC [target: SelectionId, targetSel, srcSel: Selection] = {
IF ~CheckReadonly[targetSel]
THEN {
Deselect[selection: secondary]; RETURN };
IF targetSel.data.tsInfo#
NIL
AND
(~TEditProfile.editTypeScripts
OR TEditImpl.CaretAtEnd[targetSel]
) THEN
BEGIN
special copy to typescript unless we are editing typescripts like regular Tioga documents and the target caret is at the end
tSel: Selection ← Alloc[];
tSel1: Selection ← Alloc[];
span: TextNode.Span ← [srcSel.start.pos, srcSel.end.pos];
TEditSelection.Copy[source: sSel, dest: oldSel]; -- save the secondary selection for Repeat's
-- force selection to end of typescript
TEditSelection.Copy[source: targetSel, dest: tSel];
tSel.insertion ← before;
tSel.granularity ← point;
tSel.start.pos ← tSel.end.pos ← TextNode.LastLocWithin[tSel.data.text];
TEditSelection.Copy[source: srcSel, dest: tSel1]; srcSel ← tSel1;
Deselect[selection: primary];
Deselect[selection: secondary];
CopyToTypeScript[tSel, span];
IF target=primary
THEN {
-- leave primary as caret at end of typescript
tSel.start.pos ← tSel.end.pos ← TextNode.LastLocWithin[tSel.data.text];
MakeSelection[selection: primary, new: tSel] }
ELSE MakeSelection[selection: primary, new: srcSel];
Free[tSel]; Free[tSel1];
END
ELSE IF srcSel.pendingDelete THEN Move[target]
ELSE CopyToDoc[targetSel, srcSel, target];
};
Paste:
PUBLIC
PROC = {
DoPaste:
PROC [root: TextEdit.Ref, tSel: Selection] = {
source: TextNode.Span ← EditSpan.SavedForPaste[];
tdd: TEditDocument.TEditDocumentData ← tSel.data;
IF source = TextNode.nullSpan OR tSel.viewer=NIL THEN GOTO Bad;
IF tdd.tsInfo=
NIL
AND tSel.pendingDelete
THEN {
DoPendingDelete[];
TEditSelection.Copy[source: pSel, dest: tSel] };
Deselect[selection: secondary];
-- now create a phony secondary selection for Copy
tSel.start.pos ← source.start;
tSel.end.pos ← source.end;
IF source.start.where=TextNode.NodeItself
OR source.end.where=TextNode.NodeItself
THEN { tSel.granularity ← node; UnConvertNodeSelects[tSel] }
ELSE tSel.granularity ← char;
tSel.viewer ← pSel.viewer; -- else Copy will think there isn't a secondary selection
tSel.data ← NIL;
tSel.pendingDelete ← FALSE;
DoCopy[primary, pSel, tSel];
EXITS Bad => EditFailed[] };
CallWithLocks[DoPaste] };
Move:
PUBLIC
PROCEDURE [target: SelectionId ← primary] = {
targetSel: Selection ← IF target=primary THEN pSel ELSE sSel;
srcSel: Selection ← IF target=primary THEN sSel ELSE pSel;
DoMove:
PROC [sourceRoot, destRoot: TextEdit.Ref, tSel, srcSel, targetSel: Selection] = {
nodeMove: BOOLEAN;
pDel: BOOLEAN;
wordMode: BOOLEAN = FALSE; -- (srcSel.granularity = word);
IF GetSelectionGrain[srcSel] = node
THEN {
-- see if moving entire contents
newSelNode: TextNode.Ref ← TextNode.StepForward[srcSel.end.pos.node];
IF newSelNode=
NIL
THEN {
-- moving the last node of the doc
newSelNode ← TextNode.StepBackward[srcSel.start.pos.node];
IF (newSelNode=
NIL
OR newSelNode=sourceRoot)
AND destRoot # sourceRoot
THEN {
-- moving all the nodes to different tree
child: TextEdit.Ref ← TextNode.FirstChild[sourceRoot];
srcSel.start.pos.node ← child; -- make sure doesn't include the root
[] ← EditSpan.InsertTextNode[sourceRoot, child, before, FALSE, TEditInput.currentEvent] }}};
nodeMove ← ConvertNodeSelects[srcSel];
IF (pDel ← tSel.pendingDelete)
THEN {
-- move source onto target
[] ← ConvertNodeSelects[tSel];
[[tSel.start.pos, tSel.end.pos]] ← EditSpan.MoveOnto[
destRoot, sourceRoot, [tSel.start.pos, tSel.end.pos],
[srcSel.start.pos, srcSel.end.pos], wordMode,
TRUE, TEditInput.currentEvent !
EditSpan.CannotDoEdit => GOTO Bad];
tSel.pendingDelete ← FALSE }
ELSE {
-- move source to target caret
loc: TextNode.Location ← InsertionPoint[tSel];
unnest: INTEGER ← 0; -- amount to unnest by if moving nodes after
where: EditSpan.Place ← IF tSel.insertion = before THEN before ELSE after;
IF nodeMove
THEN {
-- don't move nodes into target node
IF where = before
AND loc.where > 0
AND
loc.where = TextEdit.Size[TextNode.NarrowToTextNode[loc.node]]
THEN
where ← after; -- caret at end of node, so move after
loc.where ← TextNode.NodeItself };
IF nodeMove
AND where=after
AND tSel.start.pos.node#tSel.end.pos.node
THEN
unnest ← TextNode.Level[tSel.end.pos.node]-TextNode.Level[tSel.start.pos.node];
[[tSel.start.pos, tSel.end.pos]] ← EditSpan.Move[
destRoot, sourceRoot, loc,
[srcSel.start.pos, srcSel.end.pos], wordMode,
where, 0, TEditInput.currentEvent !
EditSpan.CannotDoEdit => GOTO Bad];
IF unnest > 0
THEN
-- unnest so that moved span starts at same level as start of dest span
[[tSel.start.pos, tSel.end.pos]] ←
EditSpan.ChangeNesting[root: destRoot, span: [tSel.start.pos, tSel.end.pos],
change: -unnest, event: TEditInput.currentEvent !
EditSpan.CannotDoEdit => CONTINUE];
tSel.granularity ← srcSel.granularity;
UnConvertNodeSelects[tSel];
tSel.insertion ← after;
TEditSelection.Copy[source: tSel, dest: oldSel]; -- save for Repeat's
oldSel.pendingDelete ← (target=primary) OR (target=secondary AND pDel);
tSel.pendingDelete ← FALSE;
MakeSelection[selection: primary, new: tSel];
EXITS Bad => { MakeSelection[selection: primary, new: tSel]; EditFailed[] }};
CallWithBothLocked[DoMove, targetSel, srcSel, write] };
Transpose:
PUBLIC
PROCEDURE [target: SelectionId ← primary] = {
targetSel: Selection ← IF target=primary THEN pSel ELSE sSel;
srcSel: Selection ← IF target=primary THEN sSel ELSE pSel;
DoTranspose:
PROC [sourceRoot, destRoot: TextEdit.Ref, tSel, srcSel, targetSel: Selection] = {
wordMode: BOOLEAN = FALSE; -- targetSel.granularity=word AND srcSel.granularity=word;
tempT: TextNode.Span;
[] ← ConvertNodeSelects[srcSel];
[] ← ConvertNodeSelects[targetSel];
[tempT,
----] ← EditSpan.Transpose[destRoot, sourceRoot,
[targetSel.start.pos, targetSel.end.pos],
[srcSel.start.pos, srcSel.end.pos],
wordMode, TEditInput.currentEvent ! EditSpan.CannotDoEdit => GOTO Bad];
[srcSel.start.pos, srcSel.end.pos] ← tempT;
UnConvertNodeSelects[srcSel];
srcSel.pendingDelete ← FALSE;
MakeSelection[selection: primary, new: srcSel];
TEditSelection.Copy[source: srcSel, dest: oldSel]; -- save for Repeat's
EXITS Bad => {
MakeSelection[selection: primary, new: IF target=primary THEN targetSel ELSE srcSel];
EditFailed[] }};
CallWithBothLocked[DoTranspose, targetSel, srcSel, write] };
Break:
PUBLIC
PROC = {
DoBreak:
PROC [root: TextEdit.Ref, tSel: Selection] = {
null: BOOL ← FALSE;
caret: TextNode.Location;
newNode: TextNode.RefTextNode;
IF tSel.pendingDelete
THEN {
DoPendingDelete[];
TEditSelection.Copy[source: pSel, dest: tSel] };
caret ← InsertionPoint[pSel];
Deselect[primary];
newNode ← TextNode.NarrowToTextNode[EditSpan.Split[root,
caret, TEditInput.currentEvent ! EditSpan.CannotDoEdit => GOTO Bad]];
IF newNode #
NIL
AND TextEdit.Size[TextNode.NarrowToTextNode[caret.node]]=0
AND
TextEdit.Size[newNode] > 0 THEN null ← TRUE -- caret was at front of nonempty node
ELSE tSel.start.pos.node ← newNode; -- move caret to start of new node
tSel.start.pos.where ← 0;
tSel.end.pos ← tSel.start.pos;
tSel.granularity ← point;
tSel.insertion ← before;
tSel.pendingDelete ← FALSE;
tSel.looks ← TextLooks.noLooks;
MakeSelection[selection: primary, new: tSel];
CheckStartLine[viewer: tSel.viewer, old: caret, new: [newNode,0], null: null];
EXITS Bad => { MakeSelection[selection: primary, new: tSel]; EditFailed[] }};
CallWithLocks[DoBreak] };
Join:
PUBLIC
PROCEDURE = {
DoJoin:
PROC [root: TextEdit.Ref, tSel: Selection] = {
loc: TextNode.Location;
pred: TextNode.Ref;
node: TextNode.RefTextNode ← TextNode.NarrowToTextNode[InsertionPoint[].node];
IF node=
NIL
OR (pred ← TextNode.StepBackward[node])=
NIL
OR
TextNode.Parent[pred]=NIL --i.e., pred is root-- THEN { EditFailed[]; RETURN };
Deselect[primary];
loc ← EditSpan.Merge[root, node, TEditInput.currentEvent !
EditSpan.CannotDoEdit => GOTO Bad];
MakePointSelection[tSel, loc];
CheckStartLine[viewer: tSel.viewer, old: [node,0], new: loc];
EXITS Bad => { MakeSelection[selection: primary, new: tSel]; EditFailed[] }};
CallWithLocks[DoJoin] };
CheckStartLine:
PROC
[viewer: ViewerClasses.Viewer, old, new: TextNode.Location, null: BOOL ← FALSE] = {
first: BOOLEAN ← TRUE;
FOR v: ViewerClasses.Viewer ← viewer, v.link
UNTIL v=
NIL
OR (v=viewer
AND ~first)
DO
tdd: TEditDocument.TEditDocumentData ← NARROW[v.data];
IF tdd #
NIL
THEN {
vloc: TextNode.Location ← tdd.lineTable.lines[0].pos;
first ← FALSE;
IF vloc.node = old.node
AND vloc.where >= old.where
THEN {
vnew: TextNode.Location ← [new.node, new.where+vloc.where-old.where];
IF null AND vnew.where = 0 THEN vnew.node ← old.node;
TEditDisplay.EstablishLine[tdd, vnew] };
};
ENDLOOP };
SaveForPaste:
PUBLIC
PROC = {
DoSaveForPaste:
PROC [root: TextEdit.Ref, tSel: Selection] = {
[] ← ConvertNodeSelects[tSel];
EditSpan.SaveForPaste[[tSel.start.pos, tSel.end.pos], TEditInput.currentEvent] };
CallWithLocks[DoSaveForPaste, read] };
SaveSpanForPaste:
PUBLIC
PROC [
startLoc, endLoc: TextNode.Location, grain: TEditDocument.SelectionGrain] = {
root: TextEdit.Ref = TextNode.Root[startLoc.node];
lockRef: TEditLocks.LockRef;
{ENABLE UNWIND => { IF lockRef # NIL THEN TEditLocks.Unlock[root] };
lockRef ← TEditLocks.Lock[root, "SaveSpanForPaste", read];
IF grain=node
OR grain=branch
THEN {
startLoc.where ← TextNode.NodeItself; endLoc.where ← TextNode.NodeItself };
EditSpan.SaveForPaste[[startLoc, endLoc], TEditInput.currentEvent];
TEditLocks.Unlock[root] }};
Nest:
PUBLIC
PROC = { ChangeNesting[1] };
-- move the selection to a deeper nesting level in the tree
UnNest:
PUBLIC
PROC = { ChangeNesting[-1] };
-- move the selection to a shallower nesting level in the tree
ChangeNesting:
PROC [change:
INTEGER] = {
DoChangeNesting:
PROC [root: TextEdit.Ref, tSel: Selection] = {
Deselect[primary];
[] ← EditSpan.ChangeNesting[root,
TextNode.MakeNodeSpan[tSel.start.pos.node, tSel.end.pos.node],
change, TEditInput.currentEvent ! EditSpan.CannotDoEdit => GOTO Bad];
tSel.pendingDelete ← FALSE;
MakeSelection[selection: primary, new: tSel];
IF CaretVisible[] THEN TEditRefresh.ScrollToEndOfSel[tSel.viewer, TRUE];
EXITS Bad => { MakeSelection[selection: primary, new: tSel]; EditFailed[] }};
CallWithLocks[DoChangeNesting] };
ModifyLook:
PUBLIC
PROC [look: TextLooks.Look, op: TEditInputOps.ModifyOp] = {
DoModifyLook:
PROC [root: TextEdit.Ref, tSel: Selection] = {
remLooks, addLooks: TextLooks.Looks ← TextLooks.noLooks;
IF tSel.granularity#point
THEN {
Deselect[primary];
IF op=add THEN addLooks[look] ← TRUE ELSE remLooks[look] ← TRUE;
EditSpan.ChangeLooks[root: root,
span: [tSel.start.pos, tSel.end.pos],
remove: remLooks, add: addLooks,
event: TEditInput.currentEvent];
tSel.pendingDelete ← FALSE;
MakeSelection[selection: primary, new: tSel] };
ModifyCaretLook[look, op] };
CallWithLocks[DoModifyLook] };
ModifyCaretLook:
PUBLIC
PROC [look: TextLooks.Look, op: TEditInputOps.ModifyOp] =
BEGIN
LockSel[primary, "ModifyCaretLook"];
pSel.looks[look] ← (op=add);
IF SelAtEndOfTypeScript[pSel]
THEN
IF (op=add) THEN TypeScript.ChangeLooks[pSel.viewer, look]
ELSE TypeScript.ChangeLooks[pSel.viewer, Capital[look]];
UnlockSel[primary];
END;
GetSelLooks:
PROC [sel: Selection]
RETURNS [looks: TextLooks.Looks] = {
first: BOOLEAN ← TRUE;
GetSelLooks:
PROC [node: TextNode.RefTextNode, start, len: TextNode.Offset]
RETURNS [stop: BOOLEAN] = {
end: TextNode.Offset ← MIN[TextEdit.Size[node],start+len];
FOR i: TextNode.Offset
IN [start..end)
DO
lks: TextLooks.Looks ← TextEdit.FetchLooks[node,i];
IF first THEN { first ← FALSE; looks ← lks }
ELSE
IF lks#looks
THEN {
OPEN MessageWindow;
Append["Selection does not have uniform looks.",TRUE];
Append[" Using looks from first char."];
Blink[]; RETURN [TRUE] };
ENDLOOP;
RETURN [FALSE] };
EditSpanSupport.Apply[[sel.start.pos, sel.end.pos],GetSelLooks];
IF first THEN looks ← sel.looks -- null selection, use caret
};
ChangeLooks:
PUBLIC
PROC [add, remove: TextLooks.Looks] = {
DoChangeLooks:
PROC [root: TextEdit.Ref, tSel: Selection] = {
Deselect[primary];
ChangeSelLooks[add,remove,tSel];
MakeSelection[tSel,primary] };
CallWithLocks[DoChangeLooks] };
CopyLooks:
PUBLIC
PROCEDURE [target: SelectionId ← primary] = {
targetSel: Selection ← IF target=primary THEN pSel ELSE sSel;
srcSel: Selection ← IF target=primary THEN sSel ELSE pSel;
DoCopyLooks:
PROC [sourceRoot, destRoot: TextEdit.Ref, tSel, srcSel, targetSel: Selection] = {
TEditSelection.Copy[source: srcSel, dest: oldSel]; -- save the secondary selection for Repeat's
ChangeSelLooks[add: GetSelLooks[srcSel], remove: TextLooks.allLooks, targetSel: targetSel];
MakeSelection[IF target=primary THEN targetSel ELSE srcSel, primary] };
CallWithBothLocked[DoCopyLooks, targetSel, srcSel, read] };
TransposeLooks:
PUBLIC
PROC [target: SelectionId ← primary] = {
-- Transpose the looks of the primary and secondary selections
targetSel: Selection ← IF target=primary THEN pSel ELSE sSel;
srcSel: Selection ← IF target=primary THEN sSel ELSE pSel;
DoTransLooks:
PROC [sourceRoot, destRoot: TextEdit.Ref, tSel, srcSel, targetSel: Selection] = {
srcLooks, targetLooks: TextLooks.Looks;
srcLooks ← GetSelLooks[srcSel];
targetLooks ← GetSelLooks[targetSel];
TEditSelection.Copy[source: srcSel, dest: oldSel]; -- save for Repeat's
Deselect[primary]; Deselect[secondary];
ChangeSelLooks[add: srcLooks, remove: targetLooks, targetSel: targetSel];
ChangeSelLooks[add: targetLooks, remove: srcLooks, targetSel: srcSel];
MakeSelection[IF target=primary THEN targetSel ELSE srcSel, primary] };
CallWithBothLocked[DoTransLooks, targetSel, srcSel, write] };
ChangeSelLooks:
PROC [add, remove: TextLooks.Looks, targetSel: Selection] =
BEGIN
IF targetSel.granularity # point
THEN {
EditSpan.ChangeLooks[SelectionRoot[targetSel],
[targetSel.start.pos, targetSel.end.pos], remove, add,
TEditInput.currentEvent];
targetSel.pendingDelete ← FALSE };
targetSel.looks ← TextLooksSupport.ModifyLooks[targetSel.looks, remove, add];
AdjustTypeScriptLooks[targetSel, add, remove];
END;
ChangeCaretLooks:
PUBLIC
PROC [add, remove: TextLooks.Looks] =
BEGIN
LockSel[primary, "ChangeCaretLooks"];
pSel.looks ← TextLooksSupport.ModifyLooks[pSel.looks, remove, add];
AdjustTypeScriptLooks[pSel, add, remove];
UnlockSel[primary];
END;
SelAtEndOfTypeScript:
PROC [targetSel: Selection]
RETURNS [
BOOL] = {
tdd: TEditDocumentData;
IF targetSel.viewer=NIL THEN RETURN [FALSE];
tdd ← NARROW[targetSel.viewer.data];
IF tdd = NIL OR tdd.tsInfo=NIL THEN RETURN [FALSE]; -- not a typescript
IF ~TEditImpl.CaretAtEnd[targetSel] THEN RETURN [FALSE];
RETURN [TRUE] };
Capital:
PROC [c:
CHAR]
RETURNS[
CHAR] =
INLINE {
RETURN[IF c IN ['a..'z] THEN LOOPHOLE[c - 'a + 'A] ELSE c]};
AdjustTypeScriptLooks:
PROC [targetSel: Selection, add, remove: TextLooks.Looks] =
BEGIN
IF ~SelAtEndOfTypeScript[targetSel] THEN RETURN;
FOR c:
CHAR
IN TextLooks.Look
DO
IF remove[c] THEN TypeScript.ChangeLooks[targetSel.viewer, Capital[c]];
IF add[c] THEN TypeScript.ChangeLooks[targetSel.viewer, c];
ENDLOOP;
END;
END.