DIRECTORY Basics USING [DoubleAnd, DoubleNot, DoubleOr, NonNegative], PrincOpsUtils USING [LongCopy], Rope USING [Cat, Fetch, FromChar, ROPE, Size], RunReader USING [FreeRunReader, Get, GetRunReader, Ref, SetPosition], TextLooks USING [allLooks, BaseRuns, FlatMax, Look, Looks, MaxLen, noLooks, Run, Runs, RunsBody, Tchange, Tconcat, Treplace, Tsubstr], TextLooksSupport USING []; TextLooksImpl: CEDAR PROGRAM IMPORTS Basics, PrincOpsUtils, Rope, RunReader EXPORTS TextLooks, TextLooksSupport SHARES TextLooks = BEGIN OPEN TextLooks; OutOfBounds: PUBLIC ERROR = CODE; NonNeg: PROC [x: INT] RETURNS [INT] = INLINE { RETURN[Basics.NonNegative[x]] }; CheckLongSub: PROC [x, y: INT] RETURNS [INT] = INLINE { RETURN[NonNeg[x-y]] }; ReplaceByRun: PUBLIC PROC [dest: Runs, start, len, runLen, destSize: INT, inherit: BOOL, looks: Looks] RETURNS [Runs] = { merge: BOOL _ FALSE; mergeLooks: Looks; split, numruns: NAT; flat: BaseRuns; c, numRuns, oldPos, size: INT; Count: PROC [start, len: INT] RETURNS [INT] = { IF len=0 THEN RETURN[numRuns]; [c, merge, mergeLooks] _ CountRuns[dest, start, len, FlatMax-numRuns, merge, mergeLooks]; RETURN [numRuns_numRuns+c]; }; AddIt: PROC RETURNS [INT] = { c _ IF merge AND mergeLooks=looks THEN 0 ELSE 1; merge _ TRUE; mergeLooks _ looks; RETURN [numRuns_numRuns+c]; }; Extract: PROC [start, len: INT] = { IF len > 0 THEN split _ ExtractRuns[flat, dest, start, len, split]; }; TryFlatAppendRun: PROC [base: Runs] RETURNS [Runs] = { flat: BaseRuns; size: INT; [numRuns, merge, mergeLooks] _ CountRuns[base, 0, size_Size[base], FlatMax]; IF numRuns > FlatMax OR AddIt[] > FlatMax THEN RETURN [NIL]; flat _ NewBase[numruns_numRuns]; split _ ExtractRuns[flat, base, 0, size, 0]; split _ InsertRun[flat, runLen, looks, split]; IF split # numruns THEN ERROR; IF flat[numruns-1].after # size+runLen THEN ERROR; RETURN [flat]; }; IF runLen=0 THEN RETURN [Replace[base: dest, start: start, len: len, replace: NIL, baseSize: destSize, repSize: 0, tryFlat: TRUE]]; IF inherit THEN {-- get looks from destination IF destSize = 0 THEN NULL -- take from arg list ELSE looks _ FetchLooks[dest, IF start > 0 THEN start-1 -- take from before replacement ELSE IF len=destSize THEN 0 -- replacing everything ELSE len]; -- take from after replacement }; IF dest=NIL AND looks=noLooks THEN RETURN[NIL]; numRuns _ 0; oldPos _ start+len; size _ destSize-len+runLen; IF Count[0, start] > FlatMax OR AddIt[] > FlatMax OR Count[oldPos, destSize-oldPos] > FlatMax THEN { newPos: INT _ start+runLen; replace, new: Runs; WHILE dest # NIL DO WITH dest SELECT FROM x: REF RunsBody.node.replace => { xnewPos: INT _ x.newPos; xstart: INT _ x.start; IF start <= xstart AND oldPos >= xnewPos THEN { oldPos _ x.oldPos+(oldPos-xnewPos); dest _ x.base; len _ oldPos-start; LOOP; } ELSE IF start = xnewPos -- appending to the replacement AND (new _ TryFlatAppendRun[x.replace])#NIL THEN { start _ xstart; oldPos _ x.oldPos+len; dest _ x.base; replace _ new; } }; x: REF RunsBody.node.concat => { -- try to append to first part of the concat xpos: INT _ x.pos; IF start=xpos AND len=0 AND (new _ TryFlatAppendRun[x.base])#NIL THEN RETURN [ NEW[Tconcat _ [node[concat [size, new, x.rest, xpos+runLen]]]]]; }; ENDCASE; EXIT; ENDLOOP; IF replace=NIL AND (replace _ CreateRun[runLen, looks])=NIL THEN replace _ MakeRun[runLen]; IF dest=NIL THEN dest _ MakeRun[destSize]; RETURN [NEW[Treplace _ [node[replace[size, dest, replace, start, oldPos, newPos]]]]] }; IF numRuns=0 THEN RETURN[NIL]; flat _ NewBase[numruns_numRuns]; split _ 0; Extract[0, start]; split _ InsertRun[flat, runLen, looks, split]; Extract[oldPos, destSize-oldPos]; IF split # numruns THEN ERROR; IF flat[numruns-1].after # size THEN ERROR; RETURN [flat] }; CountRuns: PUBLIC PROC [runs: Runs, start, len: INT, limit: INT _ MaxLen, merge: BOOL _ FALSE, firstLooks: Looks _ noLooks] RETURNS [count: INT, nonempty: BOOL, lastLooks: Looks] = { c: INT; count _ 0; DO nonempty _ merge; IF len=0 THEN { lastLooks _ firstLooks; RETURN }; IF runs=NIL THEN { c _ IF merge AND firstLooks=noLooks THEN 0 ELSE 1; RETURN [count+c, TRUE, noLooks] }; WITH runs SELECT FROM x: REF RunsBody.base => { first, last: NAT; len _ MIN[len, CheckLongSub[TbaseSize[x], start]]; [first, last] _ FindBaseRuns[x, start, len]; c _ last-first+1; IF merge AND firstLooks=x[first].looks THEN c _ c-1; RETURN [count+c, TRUE, x[last].looks] }; x: REF RunsBody.node.substr => { len _ MIN[len, CheckLongSub[x.size, start]]; start _ start + x.start; runs _ x.base; LOOP }; x: REF RunsBody.node.concat => { xpos: INT _ x.pos; len _ MIN[len, CheckLongSub[x.size, start]]; IF start < xpos THEN { subLen: INT _ xpos - start; IF len <= subLen THEN { runs _ x.base; LOOP }; [c, merge, firstLooks] _ CountRuns[ x.base, start, subLen, limit, merge, firstLooks]; count _ count+c; IF c > limit THEN RETURN; limit _ limit-c; start _ xpos; len _ len-subLen; }; start _ start-xpos; runs _ x.rest; LOOP }; x: REF RunsBody.node.replace => { xstart: INT _ x.start; xnew: INT _ x.newPos; len _ MIN[len, CheckLongSub[x.size, start]]; IF start < xstart THEN { subLen: INT _ xstart - start; IF len <= subLen THEN {runs _ x.base; LOOP}; [c, merge, firstLooks] _ CountRuns[ x.base, start, subLen, limit, merge, firstLooks]; count _ count+c; IF c > limit THEN RETURN; limit _ limit-c; start _ xstart; len _ len-subLen; }; IF start < xnew THEN { st: INT _ start - xstart; subLen: INT _ xnew - start; IF len <= subLen THEN { start _ st; runs _ x.replace; LOOP }; [c, merge, firstLooks] _ CountRuns[ x.replace, st, subLen, limit, merge, firstLooks]; count _ count+c; IF c > limit THEN RETURN; limit _ limit-c; start _ xnew; len _ len-subLen }; start _ start - xnew + x.oldPos; runs _ x.base; LOOP }; x: REF RunsBody.node.change => { xstart: INT _ x.start; xend, subLen: INT; len _ MIN[len, CheckLongSub[x.size, start]]; IF start < xstart THEN { IF len <= (subLen _ xstart-start) THEN {runs _ x.base; LOOP}; [c, merge, firstLooks] _ CountRuns[ x.base, start, subLen, limit, merge, firstLooks]; count _ count+c; IF c > limit THEN RETURN; limit _ limit-c; start _ xstart; len _ len-subLen; }; IF start < (xend _ xstart+x.len) THEN { subLen _ MIN[xend-start, len]; [c, merge, firstLooks] _ CountRunsAfterChanges[ x.base, start, subLen, limit, x.remove, x.add, merge, firstLooks]; count _ count+c; IF c > limit THEN RETURN; limit _ limit-c; start _ xend; len _ len-subLen; }; runs _ x.base; LOOP }; ENDCASE => ERROR; ENDLOOP; }; ExtractRuns: PUBLIC PROC [base: BaseRuns, ref: Runs, start, len: INT, index: NAT _ 0] RETURNS [NAT] = TRUSTED { -- value is next index DO IF len=0 THEN RETURN [index]; IF ref=NIL THEN -- treat as noLooks RETURN [InsertRun[base, len, noLooks, index]]; WITH ref SELECT FROM x: REF RunsBody.base => { firstLen, lastLen, xloc, next, loc: INT; first, last: NAT; len _ MIN[len, CheckLongSub[TbaseSize[x], start]]; [first, last] _ FindBaseRuns[x, start, len]; [firstLen, lastLen] _ BaseRunLengths[x, start, len, first, last]; IF index=0 THEN { -- this is the first run to be extracted loc _ firstLen; base[0] _ [loc, x[first].looks]; index _ 1; } ELSE { loc _ base[index-1].after + firstLen; IF base[index-1].looks=x[first].looks -- merge runs THEN base[index-1].after _ loc ELSE { base[index] _ [loc, x[first].looks]; index _ index+1 } }; IF first=last THEN RETURN [index]; IF (xloc _ x[first].after) = loc THEN { -- can simply copy runs numRuns: NAT; IF (numRuns _ last-first-1) > 0 THEN { CopyRuns[to:base, toLoc:index, from:x, fromLoc:first+1, nRuns: numRuns]; index _ index+numRuns; loc _ base[index-1].after } } ELSE FOR i: NAT IN (first..last) DO loc _ loc + (next _ x[i].after) - xloc; xloc _ next; base[index] _ [loc, x[i].looks]; index _ index+1; ENDLOOP; base[index] _ [loc+lastLen, x[last].looks]; RETURN [index+1] }; x: REF RunsBody.node.substr => { len _ MIN[len, CheckLongSub[x.size, start]]; start _ start + x.start; ref _ x.base; LOOP }; x: REF RunsBody.node.concat => { xpos: INT _ x.pos; len _ MIN[len, CheckLongSub[x.size, start]]; IF start < xpos THEN { subLen: INT _ xpos - start; IF len <= subLen THEN { ref _ x.base; LOOP }; index _ ExtractRuns[base, x.base, start, subLen, index]; start _ xpos; len _ len-subLen }; start _ start-xpos; ref _ x.rest; LOOP }; x: REF RunsBody.node.replace => { xstart: INT _ x.start; xnew: INT _ x.newPos; len _ MIN[len, CheckLongSub[x.size, start]]; IF start < xstart THEN { subLen: INT _ xstart - start; IF len <= subLen THEN {ref _ x.base; LOOP}; index _ ExtractRuns[base, x.base, start, subLen, index]; start _ xstart; len _ len-subLen }; IF start < xnew THEN { st: INT _ start - xstart; subLen: INT _ xnew - start; IF len <= subLen THEN { start _ st; ref _ x.replace; LOOP }; index _ ExtractRuns[base, x.replace, st, subLen, index]; start _ xnew; len _ len-subLen }; start _ start - xnew + x.oldPos; ref _ x.base; LOOP }; x: REF RunsBody.node.change => { xstart: INT _ x.start; xend, subLen: INT; len _ MIN[len, CheckLongSub[x.size, start]]; IF start < xstart THEN { IF len <= (subLen _ xstart-start) THEN {ref _ x.base; LOOP}; index _ ExtractRuns[base, x.base, start, subLen, index]; start _ xstart; len _ len-subLen }; IF start < (xend _ xstart+x.len) THEN { subLen _ MIN[xend-start, len]; index _ ExtractRunsAfterChanges[ base, x.base, x.remove, x.add, start, subLen, index]; start _ xend; len _ len-subLen }; ref _ x.base; LOOP }; ENDCASE => ERROR; ENDLOOP }; NewBase: PUBLIC PROC [runs: NAT] RETURNS [BaseRuns] = { RETURN [NEW[base RunsBody[runs]]]; }; BaseRun: PUBLIC PROC [x: BaseRuns, index: INT, lower: NAT _ 0, upper: NAT _ LAST[NAT]] RETURNS [NAT] = { len: NAT; size: INT; IF index = 0 THEN RETURN [0]; IF (len_x.length) <= 1 THEN RETURN [0]; IF index+1 >= (size_TbaseSize[x]) THEN RETURN[len-1]; IF upper >= len THEN upper _ len-1; IF lower > 0 AND x[lower-1].after > index THEN lower _ 0; DO -- always know index is in run between lower and upper inclusive run: NAT _ (upper+lower)/2; IF index < x[run].after THEN upper _ run ELSE lower _ run+1; IF upper=lower THEN RETURN[upper]; ENDLOOP }; CopyRuns: PUBLIC PROC [to, from: BaseRuns, toLoc, fromLoc, nRuns: NAT] = TRUSTED { RunsOffset: NAT = SIZE[base RunsBody[0]]; nLeft: NAT; IF nRuns=0 THEN RETURN; IF fromLoc >= from.length OR toLoc >= to.length THEN ERROR; nLeft _ nRuns-1; to[toLoc+nLeft] _ from[fromLoc+nLeft]; -- bounds check PrincOpsUtils.LongCopy[ from: LOOPHOLE[from, LONG POINTER]+fromLoc*SIZE[Run]+RunsOffset, to: LOOPHOLE[to, LONG POINTER]+toLoc*SIZE[Run]+RunsOffset, nwords: nLeft*SIZE[Run]] }; InsertRun: PUBLIC PROC [base: BaseRuns, len: INT, looks: Looks, index: NAT] RETURNS [NAT] = { -- value is next index IF index=0 THEN { base[0] _ [len, looks]; index _ 1 } ELSE { loc: INT _ base[index-1].after + len; IF base[index-1].looks=looks -- merge runs THEN base[index-1].after _ loc ELSE { base[index] _ [loc, looks]; index _ index+1 } }; RETURN [index] }; FindBaseRuns: PUBLIC PROC [x: BaseRuns, start, len: INT] RETURNS [first, last: NAT] = { first _ BaseRun[x, start]; last _ IF len>1 THEN BaseRun[x, start+len-1, first] ELSE first }; BaseRunLengths: PUBLIC PROC [x: BaseRuns, start, len: INT, first, last: NAT] RETURNS [firstLen, lastLen: INT] = { IF first=last THEN RETURN[len, len]; RETURN[x[first].after-start, start+len-x[last-1].after] }; And: PROC [a, b: Looks] RETURNS [Looks] ~ INLINE { RETURN[LOOPHOLE[Basics.DoubleAnd[LOOPHOLE[a], LOOPHOLE[b]]]]; }; Or: PROC [a, b: Looks] RETURNS [Looks] ~ INLINE { RETURN[LOOPHOLE[Basics.DoubleOr[LOOPHOLE[a], LOOPHOLE[b]]]]; }; Not: PROC [a: Looks] RETURNS [Looks] ~ INLINE { RETURN[LOOPHOLE[Basics.DoubleNot[LOOPHOLE[a]]]]; }; LooksAND: PUBLIC PROC [looks1, looks2: Looks] RETURNS [Looks] ~ { RETURN[And[looks1, looks2]]; }; LooksOR: PUBLIC PROC [looks1, looks2: Looks] RETURNS [Looks] ~ { RETURN[Or[looks1, looks2]]; }; LooksNOT: PUBLIC PROC [looks: Looks] RETURNS [Looks] ~ { RETURN[Not[looks]]; }; ModifyLooks: PUBLIC PROC [old, remove, add: Looks] RETURNS [Looks] = { RETURN[Or[And[old, Not[remove]], add]]; }; MergeChanges: PUBLIC PROC [oldrem, oldadd, rem, add: Looks] RETURNS [newrem, newadd: Looks] = { RETURN[newrem: Or[oldrem, rem], newadd: Or[And[oldadd, Not[rem]], add]]; }; CountRunsAfterChanges: PUBLIC PROC [ref: Runs, start, len: INT, limit: INT _ MaxLen, remove, add: Looks, merge: BOOL _ FALSE, firstLooks: Looks _ noLooks] RETURNS [count: NAT, nonempty: BOOL, lastLooks: Looks] = { ChangedBaseRuns: PROC [x: BaseRuns, start, len, size: INT, remove, add: Looks, limit: INT _ MaxLen] RETURNS [count: NAT, firstLooks, lastLooks: Looks] = { first, last: NAT; IF remove=allLooks THEN RETURN [1, add, add]; [first, last] _ FindBaseRuns[x, start, len]; count _ 1; firstLooks _ lastLooks _ ModifyLooks[x[first].looks, remove, add]; FOR i: NAT IN (first..last] DO newLooks: Looks _ ModifyLooks[x[i].looks, remove, add]; IF newLooks # lastLooks THEN { IF (count _ count+1) > limit THEN RETURN; lastLooks _ newLooks }; ENDLOOP }; c: NAT; IF len=0 THEN RETURN [0, merge, firstLooks]; IF remove=allLooks THEN RETURN [ IF merge AND firstLooks=add THEN 0 ELSE 1, TRUE, add]; count _ 0; DO nonempty _ merge; IF len=0 THEN { lastLooks _ firstLooks; RETURN }; IF ref=NIL THEN { c _ IF merge AND firstLooks=add THEN 0 ELSE 1; RETURN [count+c, TRUE, add] }; WITH ref SELECT FROM x: REF RunsBody.base => { size: INT; firstLks, lastLks: Looks; len _ MIN[len, CheckLongSub[size_TbaseSize[x], start]]; [c,firstLks,lastLks] _ ChangedBaseRuns[ x,start,len,size,remove,add,limit]; IF c > limit THEN { count _ count+c; RETURN }; IF merge AND firstLooks=firstLks THEN c _ c-1; RETURN [count+c, TRUE, lastLks] }; x: REF RunsBody.node.substr => { len _ MIN[len, CheckLongSub[x.size, start]]; start _ start + x.start; ref _ x.base; LOOP}; x: REF RunsBody.node.concat => { xpos: INT _ x.pos; len _ MIN[len, CheckLongSub[x.size, start]]; IF start < xpos THEN { subLen: INT _ xpos - start; IF len <= subLen THEN { ref _ x.base; LOOP }; [c, merge, firstLooks] _ CountRunsAfterChanges[ x.base,start,subLen, limit,remove,add,merge,firstLooks]; count _ count+c; IF c > limit THEN RETURN; limit _ limit-c; start _ xpos; len _ len-subLen }; start _ start-xpos; ref _ x.rest; LOOP }; x: REF RunsBody.node.replace => { xstart: INT _ x.start; xnew: INT _ x.newPos; len _ MIN[len, CheckLongSub[x.size, start]]; IF start < xstart THEN { subLen: INT _ xstart - start; IF len <= subLen THEN {ref _ x.base; LOOP}; [c, merge, firstLooks] _ CountRunsAfterChanges[ x.base,start,subLen, limit,remove,add,merge,firstLooks]; count _ count+c; IF c > limit THEN RETURN; limit _ limit-c; start _ xstart; len _ len-subLen}; IF start < xnew THEN { st: INT _ start - xstart; subLen: INT _ xnew - start; IF len <= subLen THEN { start _ st; ref _ x.replace; LOOP}; [c, merge, firstLooks] _ CountRunsAfterChanges[ x.replace,st,subLen,limit,remove,add,merge,firstLooks]; count _ count+c; IF c > limit THEN RETURN; limit _ limit-c; start _ xnew; len _ len-subLen}; start _ start - xnew + x.oldPos; ref _ x.base; LOOP}; x: REF RunsBody.node.change => { xstart: INT _ x.start; xend, subLen: INT; len _ MIN[len, CheckLongSub[x.size, start]]; IF start < xstart THEN { IF len <= (subLen _ xstart-start) THEN {ref _ x.base; LOOP}; [c, merge, firstLooks] _ CountRunsAfterChanges[ x.base,start,subLen,limit,remove,add,merge,firstLooks]; count _ count+c; IF c > limit THEN RETURN; limit _ limit-c; start _ xstart; len _ len-subLen}; IF start < (xend _ xstart+x.len) THEN { newRemove, newAdd: Looks; [newRemove, newAdd] _ MergeChanges[x.remove, x.add, remove, add]; subLen _ MIN[xend-start,len]; [c, merge, firstLooks] _ CountRunsAfterChanges[ x.base,start,subLen, limit,newRemove,newAdd,merge,firstLooks]; count _ count+c; IF c > limit THEN RETURN; limit _ limit-c; start _ xend; len _ len-subLen}; ref _ x.base; LOOP}; ENDCASE => ERROR; ENDLOOP}; ExtractRunsAfterChanges: PUBLIC PROC [base: BaseRuns, ref: Runs, remove, add: Looks, start: INT, len: INT, index: NAT _ 0] RETURNS [NAT] = { -- value is next index IF len>0 AND remove=allLooks THEN RETURN [InsertRun[base, len, add, index]]; DO IF len=0 THEN RETURN [index]; IF ref=NIL THEN -- treat as noLooks RETURN [InsertRun[base, len, add, index]]; WITH ref SELECT FROM x: REF RunsBody.base => { first, last: NAT; firstLen, lastLen, xloc, next, loc, size: INT; newLooks, oldLooks: Looks; len _ IF (size_TbaseSize[x]) < start THEN 0 ELSE MIN[len,size-start]; [first, last] _ FindBaseRuns[x, start, len]; [firstLen, lastLen] _ BaseRunLengths[x,start,len,first,last]; oldLooks _ ModifyLooks[x[first].looks, remove, add]; IF index=0 THEN { -- this is the first run to be extracted loc _ firstLen; base[0] _ [loc, oldLooks]; index _ 1 } ELSE { loc _ base[index-1].after + firstLen; IF base[index-1].looks=oldLooks -- merge runs THEN base[index-1].after _ loc ELSE { base[index] _ [loc, oldLooks]; index _ index+1 }}; xloc _ x[first].after; FOR i: NAT IN (first..last] DO newLooks _ ModifyLooks[x[i].looks, remove, add]; next _ IF i=last THEN xloc+lastLen ELSE x[i].after; loc _ loc+next-xloc; xloc _ next; IF newLooks # oldLooks THEN { base[index] _ [loc, newLooks]; oldLooks _ newLooks; index _ index+1 } ELSE base[index-1].after _ loc; ENDLOOP; RETURN [index] }; x: REF RunsBody.node.substr => { len _ MIN[len, CheckLongSub[x.size, start]]; start _ start + x.start; ref _ x.base; LOOP}; x: REF RunsBody.node.concat => { xpos: INT _ x.pos; len _ MIN[len, CheckLongSub[x.size, start]]; IF start < xpos THEN { subLen: INT _ xpos - start; IF len <= subLen THEN { ref _ x.base; LOOP }; index _ ExtractRunsAfterChanges[ base,x.base,remove,add,start,subLen,index]; start _ xpos; len _ len-subLen }; start _ start-xpos; ref _ x.rest; LOOP }; x: REF RunsBody.node.replace => { xstart: INT _ x.start; xnew: INT _ x.newPos; len _ MIN[len, CheckLongSub[x.size, start]]; IF start < xstart THEN { subLen: INT _ xstart - start; IF len <= subLen THEN {ref _ x.base; LOOP}; index _ ExtractRunsAfterChanges[ base,x.base,remove,add,start,subLen,index]; start _ xstart; len _ len-subLen}; IF start < xnew THEN { st: INT _ start - xstart; subLen: INT _ xnew - start; IF len <= subLen THEN { start _ st; ref _ x.replace; LOOP}; index _ ExtractRunsAfterChanges[ base,x.replace,remove,add,st,subLen,index]; start _ xnew; len _ len-subLen}; start _ start - xnew + x.oldPos; ref _ x.base; LOOP}; x: REF RunsBody.node.change => { xstart: INT _ x.start; xend, subLen: INT; len _ MIN[len, CheckLongSub[x.size, start]]; IF start < xstart THEN { IF len <= (subLen _ xstart-start) THEN {ref _ x.base; LOOP}; index _ ExtractRunsAfterChanges[ base,x.base,remove,add,start,subLen,index]; start _ xstart; len _ len-subLen}; IF start < (xend _ xstart+x.len) THEN { newRemove, newAdd: Looks; [newRemove,newAdd] _ MergeChanges[x.remove,x.add,remove,add]; subLen _ MIN[xend-start,len]; index _ ExtractRunsAfterChanges[ base,x.base,newRemove,newAdd,start,subLen,index]; start _ xend; len _ len-subLen}; ref _ x.base; LOOP}; ENDCASE => ERROR; ENDLOOP; }; LooksStats: PUBLIC PROC [base: Runs, start: INT _ 0, len: INT _ MaxLen] RETURNS [size, pieces, depth: INT] = { rem, altDepth, subSize, subDepth, subPieces: INT; size _ 0; rem _ Size[base] - start; altDepth _ 0; IF len > rem THEN len _ rem; pieces _ depth _ 0; WHILE len > 0 DO x: Runs _ base; WITH base SELECT FROM x: REF RunsBody.base => { first, last: NAT; [first,last] _ FindBaseRuns[x,start,len]; RETURN [size+last-first+1,pieces+1,MAX[depth,altDepth]] }; xNode: REF RunsBody.node => { depth _ depth+1; WITH xNode SELECT FROM x: REF RunsBody.node.substr => {base _ x.base; start _ start + x.start; LOOP}; x: REF RunsBody.node.concat => {subLen: INT _ x.pos - start; IF subLen > 0 THEN {IF len <= subLen THEN {base _ x.base; LOOP}; [subSize,subPieces,subDepth] _ LooksStats[x.base, start, subLen]; pieces _ pieces+subPieces; size _ size+subSize; altDepth _ MAX[altDepth,depth+subDepth]; len _ len - subLen; start _ 0} ELSE start _ -subLen; base _ x.rest; LOOP}; x: REF RunsBody.node.replace => {xstart: INT _ x.start; len1: INT _ xstart - start; base _ x.base; IF len1 > 0 THEN {-- a piece in first section IF len1 >= len THEN LOOP; -- only in first section [subSize,subPieces,subDepth] _ LooksStats[base, start, len1]; pieces _ pieces+subPieces; size _ size+subSize; altDepth _ MAX[altDepth,depth+subDepth]; start _ xstart; len _ len - len1; len1 _ 0}; {xpos: INT _ x.newPos; len2: INT _ xpos - start; IF len2 <= 0 THEN {-- no piece in middle section start _ x.oldPos - len2; LOOP}; base _ x.replace; start _ -len1; IF len2 >= len THEN LOOP; -- only in middle section [subSize,subPieces,subDepth] _ LooksStats[base, start, len2]; pieces _ pieces+subPieces; size _ size+subSize; altDepth _ MAX[altDepth,depth+subDepth]; base _ x.base; start _ x.oldPos; len _ len - len2; }}; x: REF RunsBody.node.change => {base _ x.base; LOOP}; ENDCASE => ERROR }; ENDCASE => ERROR; ENDLOOP; RETURN [0,0,0]; }; TbaseSize: PUBLIC PROC [x: BaseRuns] RETURNS [INT] = { RETURN [IF x.length=0 THEN 0 ELSE x[x.length-1].after] }; LooksToRope: PUBLIC PROC [looks: Looks] RETURNS [rope: Rope.ROPE] = { FOR lk: Look IN Look DO IF looks[lk] THEN rope _ Rope.Cat[rope, Rope.FromChar[lk]]; ENDLOOP; }; RopeToLooks: PUBLIC PROC [rope: Rope.ROPE] RETURNS [looks: Looks] = { looks _ noLooks; FOR i: INT IN [0..Rope.Size[rope]) DO char: CHAR _ Rope.Fetch[rope, i]; IF char IN Look THEN looks[char] _ TRUE; ENDLOOP; }; Size: PUBLIC PROC [base: Runs] RETURNS [size: INT] = { RETURN [IF base = NIL THEN 0 ELSE WITH base SELECT FROM x: REF RunsBody.base => IF x.length=0 THEN 0 ELSE x[x.length-1].after, x: REF RunsBody.node.substr => x.size, x: REF RunsBody.node.concat => x.size, x: REF RunsBody.node.replace => x.size, x: REF RunsBody.node.change => x.size, ENDCASE => ERROR ] }; Substr: PUBLIC PROC [base: Runs, start: INT, len: INT] RETURNS [new: Runs] = { DO IF base=NIL OR len=0 THEN RETURN[NIL]; WITH base SELECT FROM x: REF RunsBody.base => { rem: INT; IF (rem _ TbaseSize[x]-start) <= len THEN IF start = 0 THEN RETURN [base] ELSE len _ rem; }; x: REF RunsBody.node.substr => { rem: INT; IF (rem _ CheckLongSub[x.size, start]) <= len THEN IF start = 0 THEN RETURN [base] ELSE len _ rem; start _ start + x.start; base _ x.base; LOOP; }; x: REF RunsBody.node.concat => { xpos, rem: INT; IF (rem _ CheckLongSub[x.size, start]) <= len THEN IF start = 0 THEN RETURN [base] ELSE len _ rem; IF start >= (xpos _ x.pos) THEN { start _ start - xpos; base _ x.rest; LOOP }; IF xpos >= start+len THEN {base _ x.base; LOOP}; }; x: REF RunsBody.node.replace => { xstart, xnew, rem: INT; IF (rem _ CheckLongSub[x.size, start]) <= len THEN IF start = 0 THEN RETURN [base] ELSE len _ rem; IF start >= (xnew _ x.newPos) THEN { start _ start - xnew + x.oldPos; base _ x.base; LOOP }; IF (rem _ start+len) <= (xstart _ x.start) THEN { base _ x.base; LOOP }; IF start >= xstart AND rem <= xnew THEN { start _ start - xstart; base _ x.replace; LOOP }; }; x: REF RunsBody.node.change => { xstart: INT _ x.start; xend: INT _ xstart+x.len; IF start >= xend OR start+len <= xstart THEN { base _ x.base; LOOP }; }; ENDCASE => ERROR; IF (new _ TryFlatSubstr[base, start, len]) # NIL THEN RETURN; EXIT; ENDLOOP; IF base=NIL THEN ERROR; RETURN [NEW[Tsubstr _ [node[substr[len, base, start]]]]]; }; TryFlatSubstr: PUBLIC PROC [base: Runs, start, len: INT, limit: INT _ FlatMax] RETURNS [BaseRuns] = { -- return NIL if couldn't flatten count: INT; numruns: NAT; flat: BaseRuns; [count, , ] _ CountRuns[base, start, len, limit]; IF count > limit THEN RETURN [NIL]; flat _ NewBase[numruns_count]; IF ExtractRuns[flat, base, start, len] # numruns THEN ERROR; IF flat[numruns-1].after # len THEN ERROR; RETURN [flat]; }; Flatten: PUBLIC PROC [base: Runs] RETURNS [new: Runs] = { size, half: INT; IF base=NIL THEN RETURN [NIL]; WITH base SELECT FROM x: REF RunsBody.base => RETURN [x]; -- already flat ENDCASE => NULL; new _ TryFlatSubstr[base, 0, Size[base], 8000]; IF new#NIL THEN RETURN; -- else was too big to flatten in one piece half _ (size _ Size[base])/2; -- flatten the halves RETURN [Concat[ Flatten[Substr[base, 0, half]], Flatten[Substr[base, half, size]], half, size-half]]; }; Concat: PUBLIC PROC [base, rest: Runs, baseLen, restLen: INT] RETURNS [new: Runs] = TRUSTED { c, numRuns, size, flatLen: INT; split: NAT; merge: BOOL; looks: Looks; IF base=NIL AND rest=NIL THEN RETURN[NIL]; IF restLen=0 THEN RETURN [base]; IF baseLen=0 THEN RETURN [rest]; size _ baseLen+restLen; [numRuns, merge, looks] _ CountRuns[base, 0, baseLen, FlatMax]; IF numRuns <= FlatMax THEN { -- try flattening base IF (new _ TryFlatConcatRest[base, rest, baseLen, restLen, numRuns, merge, looks]) # NIL THEN RETURN; IF rest # NIL THEN WITH rest SELECT FROM x: REF RunsBody.node.concat => { -- try to combine base & rest.base [c, , ] _ CountRuns[x.base, 0, x.pos, FlatMax-numRuns, merge, looks]; IF (numRuns _ numRuns+c) <= FlatMax THEN { -- flatten numruns: NAT; flat: BaseRuns _ NewBase[numruns_numRuns]; split _ ExtractRuns[flat, base, 0, baseLen]; IF ExtractRuns[flat, x.base, 0, x.pos, split] # numruns THEN ERROR; flatLen _ baseLen+x.pos; IF flat[numruns-1].after # flatLen THEN ERROR; RETURN[NEW[Tconcat _ [node[concat [size, flat, x.rest, flatLen]]]]] } }; ENDCASE => NULL; }; IF base # NIL THEN WITH base SELECT FROM x: REF RunsBody.node.concat => { -- try to combine base.rest & rest baseRestLen: INT _ baseLen-x.pos; [numRuns, merge, looks] _ CountRuns[x.rest, 0, baseRestLen, FlatMax]; IF numRuns <= FlatMax THEN { [c, , ] _ CountRuns[rest, 0, restLen, FlatMax-numRuns, merge, looks]; IF (numRuns _ numRuns+c) <= FlatMax THEN { -- flatten numruns: NAT; flat: BaseRuns _ NewBase[numruns_numRuns]; split _ ExtractRuns[flat, x.rest, 0, baseRestLen]; IF ExtractRuns[flat, rest, 0, restLen, split] # numruns THEN ERROR; IF flat[numruns-1].after # baseRestLen+restLen THEN ERROR; RETURN[NEW[Tconcat _ [node[concat [size, x.base, flat, x.pos]]]]] } } }; x: REF RunsBody.node.substr => { WITH rest SELECT FROM y: REF RunsBody.node.substr => { IF x.base = y.base AND x.start+x.size = y.start THEN -- join them RETURN[NEW[Tsubstr _ [node[substr[size, x.base, x.start]]]]]; }; ENDCASE => NULL; }; ENDCASE => NULL; IF base=NIL THEN base _ MakeRun[baseLen]; IF rest=NIL THEN rest _ MakeRun[restLen]; RETURN[NEW[Tconcat _ [node[concat[size, base, rest, baseLen]]]]]; }; TryFlatConcat: PUBLIC PROC [base, rest: Runs, baseLen, restLen: INT] RETURNS [new: BaseRuns] = { -- returns NIL if too big to flatten numRuns: INT; merge: BOOL; looks: Looks; [numRuns, merge, looks] _ CountRuns[base, 0, baseLen, FlatMax]; IF numRuns > FlatMax THEN RETURN [NIL]; RETURN [TryFlatConcatRest[base, rest, baseLen, restLen, numRuns, merge, looks]]; }; TryFlatConcatRest: PUBLIC PROC [base, rest: Runs, baseLen, restLen, numRuns: INT, merge: BOOL, looks: Looks] RETURNS [BaseRuns] = { -- returns NIL if too big to flatten c: INT; split, numruns: NAT; flat: BaseRuns; [c, , ] _ CountRuns[rest, 0, restLen, FlatMax-numRuns, merge, looks]; IF (numRuns _ numRuns+c) > FlatMax THEN RETURN [NIL]; flat _ NewBase[numruns_numRuns]; split _ ExtractRuns[flat, base, 0, baseLen]; IF ExtractRuns[flat, rest, 0, restLen, split] # numruns THEN ERROR; IF flat[numruns-1].after # baseLen+restLen THEN ERROR; RETURN [flat]; }; Replace: PUBLIC PROC [ base: Runs, start, len: INT, replace: Runs, baseSize, repSize: INT, tryFlat: BOOL _ TRUE] RETURNS [new: Runs] = { oldPos, newPos, size: INT; IF base=NIL AND replace=NIL THEN RETURN [NIL]; oldPos _ start+len; newPos _ start+repSize; size _ baseSize-len+repSize; IF repSize=0 THEN -- deleting IF base=NIL OR (start=0 AND len=baseSize) THEN RETURN[NIL] ELSE IF len=0 THEN RETURN[base]; IF tryFlat THEN { merge: BOOL _ FALSE; flat: BaseRuns; looks: Looks; c, numRuns: INT; split, numruns: NAT; Count: PROC [r: Runs, start, len: INT] RETURNS [INT] = TRUSTED { IF len=0 THEN RETURN[numRuns]; [c, merge, looks] _ CountRuns[r, start, len, FlatMax-numRuns, merge, looks]; RETURN [numRuns_numRuns+c] }; Extract: PROC [r: Runs, start, len: INT] = TRUSTED { IF len > 0 THEN split _ ExtractRuns[flat, r, start, len, split] }; numRuns _ 0; IF Count[base, 0, start] <= FlatMax AND Count[replace, 0, repSize] <= FlatMax AND Count[base, oldPos, baseSize-oldPos] <= FlatMax THEN { flat _ NewBase[numruns_numRuns]; split _ 0; Extract[base, 0, start]; Extract[replace, 0, repSize]; Extract[base, oldPos, baseSize-oldPos]; IF split # numruns THEN ERROR; IF flat[numruns-1].after # size THEN ERROR; RETURN [flat] } }; WHILE base # NIL DO WITH base SELECT FROM x: REF RunsBody.node.replace => { xnewPos: INT _ x.newPos; xstart: INT _ x.start; xsize: INT; IF start <= xstart AND oldPos >= xnewPos THEN { oldPos _ x.oldPos+(oldPos-xnewPos); len _ oldPos-start; base _ x.base; LOOP } ELSE IF repSize = 0 AND start > xstart AND oldPos = xnewPos AND -- deleting end of prior replacement (new _ TryFlatSubstr[x.replace, 0, start-xstart])#NIL THEN { newPos _ start; oldPos _ x.oldPos; start _ xstart; replace _ new; base _ x.base } ELSE IF repSize = 0 AND start = xstart AND oldPos < xnewPos AND -- deleting start of prior replacement (new _ TryFlatSubstr[x.replace, len, xnewPos-oldPos])#NIL THEN { newPos _ start+xnewPos-oldPos; oldPos _ x.oldPos; replace _ new; base _ x.base } ELSE IF start = xnewPos AND -- replacing just after prior replacement (new _ TryFlatConcat[x.replace, replace, xsize_xnewPos-xstart, repSize])#NIL THEN { start _ xstart; len _ len+x.oldPos-xstart; oldPos _ start+len; repSize _ xsize+repSize; newPos _ start+repSize; replace _ new; base _ x.base; LOOP } ELSE IF start+len = xstart AND -- replacing just before prior replacement (new _ TryFlatConcat[replace, x.replace, repSize, xsize_xnewPos-xstart])#NIL THEN { len _ len+x.oldPos-xstart; oldPos _ start+len; repSize _ xsize+repSize; newPos _ start+repSize; replace _ new; base _ x.base; LOOP } }; x: REF RunsBody.node.concat => { xpos: INT _ x.pos; IF start=xpos AND len=0 THEN { -- insert between base&rest IF (new _ TryFlatConcat[x.base, replace, xpos, repSize])#NIL THEN RETURN [NEW[Tconcat _ [node[concat[size, new, x.rest, xpos+repSize]]]]]; IF (new _ TryFlatConcat[replace, x.rest, repSize, x.size-xpos])#NIL THEN RETURN [NEW[Tconcat _ [node[concat[size, x.base, new, x.pos]]]]] } }; ENDCASE => NULL; EXIT; ENDLOOP; IF base=NIL THEN base _ MakeRun[baseSize]; IF replace=NIL THEN replace _ MakeRun[repSize]; RETURN [NEW[Treplace _ [node[replace[size, base, replace, start, oldPos, newPos]]]]]; }; Copy: PUBLIC PROC [ dest: Runs, destLoc: INT, source: Runs, start, len, destSize: INT] RETURNS [Runs] = { merge: BOOL _ FALSE; flat: BaseRuns; looks: Looks; c, numRuns: INT; split, numruns: NAT; Count: PROC [base: Runs, start, len: INT] RETURNS [INT] = { IF len=0 THEN RETURN[numRuns]; [c, merge, looks] _ CountRuns[base, start, len, FlatMax-numRuns, merge, looks]; RETURN [numRuns_numRuns+c] }; Extract: PROC [base: Runs, start, len: INT] = { IF len > 0 THEN split _ ExtractRuns[flat, base, start, len, split] }; IF dest=NIL AND source=NIL THEN RETURN[NIL]; numRuns _ 0; IF Count[dest, 0, destLoc] > FlatMax OR Count[source, start, len] > FlatMax OR Count[dest, destLoc, destSize-destLoc] > FlatMax THEN RETURN [ Replace[dest, destLoc, 0, Substr[source, start, len], destSize, len, FALSE]]; IF numRuns=0 THEN RETURN [NIL]; flat _ NewBase[numruns_numRuns]; split _ 0; Extract[dest, 0, destLoc]; Extract[source, start, len]; Extract[dest, destLoc, destSize-destLoc]; IF split # numruns THEN ERROR; IF flat[numruns-1].after # destSize+len THEN ERROR; RETURN [flat]; }; CreateRun: PUBLIC PROC [len: INT, looks: Looks _ noLooks] RETURNS [new: Runs] = { base: BaseRuns; IF looks=noLooks OR len=0 THEN RETURN [NIL]; base _ NewBase[1]; base[0] _ [len, looks]; RETURN [base]; }; MakeRun: PUBLIC PROC [len: INT] RETURNS [new: Runs] = { base: BaseRuns; IF len=0 THEN RETURN [NIL]; base _ NewBase[1]; base[0] _ [len, noLooks]; RETURN [base]; }; FetchLooks: PUBLIC PROC [runs: Runs, index: INT] RETURNS [Looks] = { remove, add: Looks _ noLooks; changeLooks: BOOL _ FALSE; DO IF runs=NIL THEN RETURN [noLooks]; WITH runs SELECT FROM x: REF RunsBody.base => { looks: Looks _ x[BaseRun[x, index]].looks; IF changeLooks THEN looks _ ModifyLooks[looks, remove, add]; RETURN [looks] }; x: REF RunsBody.node.substr => IF index < x.size THEN { index _ index + x.start; runs _ x.base; LOOP }; x: REF RunsBody.node.concat => { IF index < x.size THEN { IF index < x.pos THEN {runs _ x.base; LOOP} ELSE {index _ index - x.pos; runs _ x.rest; LOOP}; }; }; x: REF RunsBody.node.replace => IF index < x.size THEN { IF index < x.start THEN {runs _ x.base; LOOP}; IF index < x.newPos THEN { index _ index - x.start; runs _ x.replace; LOOP }; index _ index - x.newPos + x.oldPos; runs _ x.base; LOOP }; x: REF RunsBody.node.change => { IF index IN [x.start..x.start+x.len) THEN { [remove, add] _ MergeChanges[x.remove, x.add, remove, add]; IF remove=allLooks THEN RETURN [add]; changeLooks _ TRUE }; runs _ x.base; LOOP }; ENDCASE => ERROR; ERROR OutOfBounds; ENDLOOP; }; ChangeLooks: PUBLIC PROC [ runs: Runs, size: INT, remove, add: Looks, start: INT _ 0, len: INT _ MaxLen] RETURNS [new: Runs] = { c, numRuns, end: INT; merge: BOOL; looks: Looks; IF runs=NIL AND add=noLooks THEN RETURN [NIL]; IF start >= size OR len=0 THEN RETURN [runs]; end _ start + (len _ MIN[len, size-start]); IF runs # NIL THEN { -- see if not really changing anything changed: BOOL _ FALSE; loc, runLen: INT _ start; runrdr: RunReader.Ref _ RunReader.GetRunReader[]; RunReader.SetPosition[runrdr, runs, start]; UNTIL loc >= end DO -- check the runs in the section to be changed lks: Looks; [runLen, lks] _ RunReader.Get[runrdr]; IF And[lks, add]#add OR And[lks, remove]#noLooks THEN { changed _ TRUE; EXIT }; loc _ loc+runLen; ENDLOOP; RunReader.FreeRunReader[runrdr]; IF NOT changed THEN RETURN [runs]; }; [numRuns, merge, looks] _ CountRuns[runs, 0, start, FlatMax]; IF numRuns <= FlatMax THEN { [c, merge, looks] _ CountRunsAfterChanges[ runs, start, len, FlatMax-numRuns, remove, add, merge, looks]; IF (numRuns _ numRuns+c) <= FlatMax THEN { [c, , ] _ CountRuns[runs, end, size-end, FlatMax-numRuns, merge, looks]; IF (numRuns _ numRuns+c) <= FlatMax THEN { split, numruns: NAT; flat: BaseRuns _ NewBase[numruns_numRuns]; split _ ExtractRuns[flat, runs, 0, start]; split _ ExtractRunsAfterChanges[flat, runs, remove, add, start, len, split]; IF ExtractRuns[flat, runs, end, size-end, split] # numruns THEN ERROR; IF flat[numruns-1].after # size THEN ERROR; RETURN [flat] } } }; IF runs # NIL THEN WITH runs SELECT FROM x: REF RunsBody.node.change => IF x.start=start AND x.len=len THEN { [remove, add] _ MergeChanges[x.remove, x.add, remove, add]; runs _ x.base }; ENDCASE => NULL; IF runs = NIL THEN runs _ MakeRun[size]; RETURN[NEW[Tchange _ [node[change[size, runs, remove, add, start, len]]]]]; }; END. TextLooksImpl.mesa Copyright c 1985, 1986 by Xerox Corporation. All rights reserved. written by Bill Paxton, February 1981 Bill Paxton, December 13, 1982 1:17 pm Maxwell, January 5, 1983 3:54 pm Russ Atkinson, July 25, 1983 3:36 pm Michael Plass, March 29, 1985 5:24:46 pm PST Doug Wyatt, September 4, 1986 6:09:19 pm PDT TextLooksBasicImpl replacing the replacement Exit the loop from here; len and runLen are not needed anymore, so don't upate the values. stops counting when exceeds limit if merge is true, then doesn't count first run if its looks=firstLooks now extract the runs modified looks are == (old & ~remove) v add ((lks & ~oldrem) v oldadd) & ~rem) v add == lks & ~(oldrem v rem)) v ((oldadd & ~rem) v add thus, newrem _ oldrem v rem, newadd _ (oldadd & ~rem) v add TextLooksSupportImpl -- stops counting when exceeds limit -- if firstSize is > 0, then tries to merge with first run -- find the runs in x in [start..start+len) -- modify looks according to remove&add -- return count of distinct runs after modify -- and looks of first & last runs after modify -- now compute count, lastLooks, and lastSize -- three pieces to consider (first, middle, last) -- a piece in middle section of replace node Rope conversion Edit operations otherwise try to break up rest see if doing concat of adjacent substr's see if adjacent to x replacing the replacement first try concat of x.base&replacement otherwise try concat of replacement&x.rest General operations returns the looks for the character at the given location Operation to change looks Κ,Ψ˜codešœ™Kšœ Οmœ7™BKšœ%™%Kšœ&™&Kšœ ™ Kšœ$™$Kšœ,™,Kšœ,™,K™—šΟk ˜ Kšœžœ0˜ž˜Cšžœžœžœ ˜K˜*——K˜—K˜—Kšžœžœ˜Kšžœ˜Kšžœ˜—Kšžœžœžœ˜*Kšžœ žœžœ˜/KšžœžœJ˜UK˜—K˜šŸœžœžœ˜Kšœžœ˜(Kšœžœ˜—šžœ ˜Kšœžœžœ˜K˜K˜ Kšœ žœ˜Kšœžœ˜š Ÿœžœžœžœžœ˜;Kšžœžœžœ ˜K˜OKšžœ˜K˜—šŸœžœžœ˜/Kšžœ žœ4˜CK˜—Kšžœžœžœžœžœžœžœ˜,K˜ Kšžœ#ž˜'Kšœ$ž˜&šœ1žœžœ˜>KšœEžœ˜M—Kšžœ žœžœžœ˜K˜+K˜7K˜)Kšžœžœžœ˜Kšžœ&žœžœ˜3Kšžœ˜K˜—K˜K™—šœ™šŸ œžœžœžœ˜9Kšžœ˜K˜Kš žœžœžœžœžœ˜,K˜K˜Kšžœ˜K˜—K˜š Ÿœžœžœžœžœ˜7K˜Kšžœžœžœžœ˜K˜K˜Kšžœ˜K˜—K˜KšŸ œžœž˜šœžœžœ ˜,Kšœ9™9K˜Kšœ žœžœ˜š žœžœžœžœžœ ˜%šžœžœž˜šœžœ˜K˜*Kšžœ žœ)˜—šžœ"žœ˜*K˜Hšžœ"žœ˜*Kšœžœ˜K˜*K˜*K˜LKšžœ9žœžœ˜FKšžœžœžœ˜+Kšžœ˜K˜—K˜—K˜—š žœžœžœžœžœž˜(š œžœžœžœ žœ˜DK˜;K˜K˜—Kšžœžœ˜—Kšžœžœžœ˜(KšžœžœA˜KK˜K˜——K˜Kšžœ˜—…—‡tΊf