-- Author: John Maxwell
-- Last Edited by: Maxwell, November 22, 1983 1:53 pm
DIRECTORY
   Beam USING [AddItem, Free, New], 
   Chord USING [AddNote, Free, New], 
   Event USING [AddNote, AddTimes, Free, KeySignature, Measure, Metrenome, Staves, Sync, TimeSignature], 
   Inline USING [LongCOPY], 
   MusicDefs, 
   Note USING [FindChord, Free, InVoice], 
   Piece USING [AddEvent, CleanUpEvents, Free, NearestEvent, New, Overflow], 
   Real USING [Fix], 
   Score USING [GetKey, GetStyle], 
   Sheet USING [FindSection, Reset], 
   Selection USING [AddLine, AddGreyLine, selection], 
   Voice USING [Correct];
PieceImplB: PROGRAM
  IMPORTS Beam, Chord, Event, Inline, MusicDefs, Note, Piece, Real, Score, Sheet, Selection, Voice 
  EXPORTS Piece = 
BEGIN
OPEN MusicDefs;
-- ****************************************************************************
-- section manipulation
-- ****************************************************************************
Merge: PUBLIC PROCEDURE[score, new: ScorePTR, begin, end: Time] = 
BEGIN ENABLE Piece.Overflow => IF score = old THEN score ← new;
l: REAL = 1;
scale: REAL;
sBegin: Time;
sync: BOOLEAN;
pBegin, pEnd: Time;
pmLast, smLast: Time ← 0;
pmFirst, smFirst: Time ← 0;
tolerance: CARDINAL = 10;
start, stop: CARDINAL ← 0;
pStop, sStop: CARDINAL ← 0;
pStart, sStart: CARDINAL ← 0;
measuresP, measuresS: INTEGER ← -1;
length: CARDINAL = new.length;
SetDirty[score, begin, end];
IF length = 0 THEN RETURN;
IF score.sheet.display = physical THEN {
MergeSection[score, new, begin, 0, length];
Piece.Free[new];
RETURN};
-- where does the score start and stop?
[start, stop] ← SelectMeasures[score, begin, end];
IF start # stop THEN begin ← score.event[start].time;
IF start # stop THEN end ← score.event[MIN[stop, score.length-1]].time+1;
Selection.AddLine[score, begin, end];
-- how are the measures in new distributed?
sync ← FALSE;
FOR i: CARDINAL IN [0..length) DO
IF new.event[i].type = sync THEN sync ← TRUE;
IF NOT Measure[new.event[i]] THEN LOOP;
IF measuresP = -1 THEN {
pmFirst ← new.event[i].time-new.event[0].time;
IF sync THEN pmFirst ← MAX[pmFirst, tolerance+1]};
sync ← FALSE;
pmLast ← new.event[length-1].time-new.event[i].time;
measuresP ← measuresP + 1;
ENDLOOP;
IF sync THEN pmLast ← MAX[pmLast, tolerance+1]; 
-- how are the measures in the score distributed?
sync ← FALSE;
FOR i: CARDINAL IN [start..stop) DO
IF NOT Measure[score.event[i]] THEN LOOP;
IF measuresS = -1 THEN {
smFirst ← score.event[i].time-score.event[start].time;
IF sync THEN smFirst ← MAX[smFirst, tolerance+1]};
sync ← FALSE;
smLast ← score.event[MIN[stop, score.length-1]].time-score.event[i].time;
measuresS ← measuresS + 1;
ENDLOOP;
IF sync THEN smLast ← MAX[smLast, tolerance+1];
-- count the partial measures 
IF pmFirst > tolerance THEN measuresP ← measuresP+1;
IF pmLast > tolerance THEN measuresP ← measuresP+1;
IF smFirst > tolerance THEN measuresS ← measuresS+1;
IF smLast > tolerance THEN measuresS ← measuresS+1;
IF smFirst <= tolerance THEN 
Selection.AddLine[score, Selection.selection.select1+smFirst+1, Selection.selection.select2];
IF smLast <= tolerance THEN 
Selection.AddLine[score, Selection.selection.select1, Selection.selection.select2-smLast-1];
IF measuresS < 1 THEN measuresS ← 1;
IF measuresP < 1 THEN measuresP ← 1;
IF measuresS # 0 AND measuresS # measuresP THEN {
score.flash ← TRUE;
Piece.Free[new]; 
RETURN};
-- merge new into the score measure by measure
pEnd ← new.event[length-1].time;
pStart ← length; sStart ← stop;
IF Measure[new.event[length-1]] THEN pStart ← length-1;
FOR i: INTEGER DECREASING IN [0..measuresP) DO
-- find corresponding measures
pStop ← pStart;
sStop ← sStart;
FOR j: CARDINAL DECREASING IN [0..pStop) DO -- find next measure
IF NOT Measure[new.event[j]] THEN LOOP;
IF pmLast IN [1..tolerance] THEN {pmLast ← 0; pStop ← pStart ← j; LOOP};
pStart ← j; EXIT;
ENDLOOP;
IF pStart = pStop THEN pStart ← 0;
FOR j: CARDINAL DECREASING IN [0..sStop) DO -- find next measure
IF NOT Measure[score.event[j]] THEN LOOP;
IF smLast IN [1..tolerance] THEN {smLast ← 0; sStop ← sStart ← j; LOOP};
sStart ← j; EXIT;
ENDLOOP;
IF sStart = sStop THEN sStart ← start;
IF pStop = pStart THEN LOOP;
-- scale new’s measure and merge it into the score
IF i = 0 THEN sBegin ← begin ELSE sBegin ← score.event[sStart].time; 
IF i # measuresP-1 THEN end ← score.event[sStop].time;
pBegin ← (IF pStart = 0 THEN 0 ELSE new.event[pStart].time);
scale ← (l*MAX[end-sBegin, 10])/(MAX[pEnd-pBegin, 10]);
scale ← MIN[scale, 1];
pEnd ← pBegin;
FOR j: CARDINAL IN [pStart..pStop) DO
new.event[j].time ← Real.Fix[scale*(new.event[j].time-pEnd)];
ENDLOOP;
MergeSection[score, new, sBegin, pStart, pStop];
ENDLOOP;
Piece.Free[new];
Voice.Correct[score, Selection.selection.select1, Selection.selection.select2]; 
Sheet.Reset[score];
END;
SelectMeasures: PROC[score: ScorePTR, begin, end: Time] RETURNS[start, stop: CARDINAL] = 
BEGIN
-- find the start
start ← score.length; stop ← 0;
FOR i: CARDINAL DECREASING IN [0..score.length) DO
IF score.event[i].time < begin AND Measure[score.event[start]]  AND start # 0 THEN EXIT;
IF score.event[i].time < begin AND score.event[i].type = sync THEN EXIT;
IF score.event[i].time < begin-40 THEN EXIT;
IF Measure[score.event[i]] OR score.event[i].type = sync THEN start ← i;
ENDLOOP;
-- find the stop
FOR i: CARDINAL IN [0..score.length] DO
IF i = score.length THEN {stop ← i; EXIT};
IF score.event[i].time > end AND Measure[score.event[stop]] AND stop # 0  THEN EXIT;
IF score.event[i].time > end AND score.event[i].type = sync THEN EXIT;
IF score.event[i].time > end+40 THEN EXIT;
IF Measure[score.event[i]] OR score.event[i].type = sync THEN stop ← i;
ENDLOOP;
IF start = score.length THEN start ← stop;
IF stop = 0 THEN stop ← start;
END;
MergeSection: PROCEDURE[score, new: ScorePTR, begin: Time, start, stop: CARDINAL] = 
BEGIN -- start and stop are indices into new, begin is the time where it goes in score
s, newSync: SyncPTR;
FOR i: CARDINAL IN [start..stop) DO
new.event[i].time ← new.event[i].time+begin;
ENDLOOP;
FOR i: CARDINAL IN [start..stop) DO
IF NOT (new.event[i].type = sync OR (new.event[i].type = staves AND Event.Staves[new.event[i]].staves # style)) THEN {zone.FREE[@new.event[i]]; LOOP};
s ← Event.Sync[score.event[Piece.NearestEvent[score, new.event[i].time, TRUE]]];
IF s = NIL OR ABS[s.time-new.event[i].time] > 1 OR new.event[i].type # sync THEN
{score ← Piece.AddEvent[score, new.event[i]]; new.event[i] ← NIL; LOOP};
newSync ← Event.Sync[new.event[i]];
FOR j: CARDINAL DECREASING IN [0..newSync.length) DO
s ← Event.AddNote[score, s, newSync.note[j]];
ENDLOOP;
zone.FREE[@new.event[i]];
ENDLOOP;
END;
     
Replace: PUBLIC PROCEDURE[score: ScorePTR, new: ScorePortionPTR, delete1, delete2: Time] = 
BEGIN ENABLE Piece.Overflow => IF score = old THEN score ← new;
 -- replaces [delete1..delete2) with the score portion. 
portion: ScorePortionRec;
IF score.sheet.voice # noVoice THEN {
DeleteSection[score, delete1, delete2, 0];
RETURN};
portion.score ← score;
SetDirty[score, delete1, LAST[Time]];
GetScoreState[@portion, delete1, delete2];
IF delete1 # delete2 THEN DeleteSection[score, delete1, delete2, portion.toc];
-- toc ← MaxToc[score, 0, begin, FALSE]-MinToc[score, end, 1000000];
-- IF score.sheet.display = physical THEN toc ← (delete2-delete1)*score.sheet.density;
IF new # NIL THEN {
InsertSection[score, new.score, delete1, new.duration, new.toc];
SetScoreDifferences[score, @portion.ss1, @new.ss1, delete1];
SetScoreDifferences[score, @new.ss2, @portion.ss2, delete1];
zone.FREE[@new]};
Sheet.Reset[score];
Selection.AddLine[score, delete1, delete1];
END;
DeleteSection: PUBLIC PROC[score: ScorePTR, delete1, delete2, toc: Time] = 
BEGIN
voice: BOOLEAN ← score.sheet.voice # noVoice;
SetDirty[score, delete1, IF voice THEN delete2 ELSE LAST[Time]];
-- free sync and invalidate syncs
FOR i: CARDINAL DECREASING IN [0..score.length) DO
IF score.event[i].time >= delete1 THEN LOOP;
IF score.event[i].time < delete2 THEN EXIT;
IF score.event[i].type = sync THEN {
sync: SyncPTR ← Event.Sync[score.event[i]];
FOR j: CARDINAL DECREASING IN [0..sync.length) DO
n: NotePTR ← sync.note[j];
IF voice THEN {IF ~Note.InVoice[n, score.sheet.voice] THEN LOOP}
ELSE { -- speed up deletion with some efficiency hacks
IF n.chord # NIL THEN Chord.Free[score, n.chord];
n.sync ← NIL}; -- so Free won’t waste time removing n from sync
Note.Free[score, n]; -- removes all back pointers to n
ENDLOOP}; 
IF ~voice AND i # 0 THEN Event.Free[score, score.event[i]]; 
ENDLOOP;
IF ~voice THEN FOR i: CARDINAL IN [0..score.length) DO -- move everything to the left
IF score.event[i].time < delete2 THEN LOOP;
Event.AddTimes[score.event[i], delete1-delete2, -toc];
ENDLOOP;
Piece.CleanUpEvents[score];
END;
InsertSection: PROCEDURE[score, new: ScorePTR, begin, duration, toc: Time] = 
BEGIN -- anything at begin ends up after new
start: CARDINAL ← 0;
length: CARDINAL = new.length;
-- move the trailing part of the score to the right
IF begin = 0 THEN begin ← 1;
-- [size, toc] ← Size[new, length];
FOR i: CARDINAL DECREASING IN [0..score.length) DO
IF score.event[i].time < begin THEN {start ← i+1; EXIT}; 
Event.AddTimes[score.event[i], duration, toc];
score.event[i+length] ← score.event[i];
ENDLOOP;
-- insert the new score
IF score.sheet.display = physical 
THEN toc ← begin*score.sheet.density 
ELSE toc ← MaxToc[score, 0, begin, TRUE];
FOR i: CARDINAL IN [start..start+length) DO
score.event[i] ← new.event[i-start];
IF score.event[i].type = sync THEN Event.AddTimes[Event.Sync[score.event[i]], begin, toc];
new.event[i-start] ← NIL; -- so Piece.Free doesn’t deallocate the syncs
ENDLOOP;
score.length ← score.length + length;
score[score.length] ← NIL;
Piece.CleanUpEvents[score];
Piece.Free[new];
Sheet.Reset[score];
IF Selection.selection.lineSelect THEN Selection.AddLine[score, begin, begin+duration];
SetDirty[score, begin, LAST[Time]];
END;
Size: PROCEDURE[score: ScorePTR, length: CARDINAL] RETURNS[size, toc: Time ← 0] = 
BEGIN
n: NotePTR;
noteTime: Time;
grey: Time = Selection.selection.greySelect2-Selection.selection.greySelect1;
FOR i: CARDINAL IN [(IF length > 10 THEN length-10 ELSE 0)..length) DO
size ← MAX[size, score.event[i].time-score.event[0].time];
IF score.event[i].type = sync THEN {
sync: SyncPTR ← Event.Sync[score.event[i]];
FOR j: CARDINAL IN [0..sync.length) DO
IF (n ← sync.note[j]) = NIL THEN EXIT;
IF n.toc = 0 THEN LOOP;
toc ← MAX[toc, n.toc+n.duration];
noteTime ← n.toc;
IF score.sheet.max-noteTime > 64000 THEN EXIT;
ENDLOOP};
ENDLOOP;
IF ABS[grey-size] < 30 THEN size ← grey ELSE size ← size+10; -- use the grey selection if applicable
IF score.sheet.display = physical THEN toc ← size*score.sheet.density;
END;
MaxToc: PUBLIC PROCEDURE[score: ScorePTR, time1, time2: Time, duration: BOOLEAN] RETURNS[Time] = 
BEGIN
n: NotePTR;
max: Time ← 0;
noteTime: Time ← end;
IF score.sheet.display = physical THEN RETURN[time2*score.sheet.density];
FOR i: CARDINAL DECREASING IN [0..score.length) DO
IF score.event[i].time >= time2 THEN LOOP;
IF score.event[i].time <= time1 THEN EXIT;
IF score.event[i].type = sync THEN {
sync: SyncPTR ← Event.Sync[score.event[i]];
FOR j: CARDINAL IN [0..sync.length) DO
IF (n ← sync.note[j]) = NIL THEN EXIT;
IF n.toc = 0 THEN LOOP;
IF n.toc > ABS[noteTime+3000] THEN LOOP;
max ← MAX[max, n.toc+(IF duration THEN n.duration ELSE 0)];
noteTime ← n.toc;
IF max-noteTime > 64000 THEN RETURN[max];
ENDLOOP};
ENDLOOP;
RETURN[max];
END;
end: Time = 10000000;
MinToc: PROCEDURE[score: ScorePTR, time1, time2: Time] RETURNS[Time] = 
BEGIN
min: Time ← end;
noteTime: Time;
n: NotePTR;
IF score.sheet.display = physical AND time1 # 0 THEN min ← time1*score.sheet.density;
FOR i: CARDINAL IN [0..score.length) DO
    IF score.event[i].time < time1 THEN LOOP;
    IF score.event[i].time > time2 THEN EXIT;
    IF score.event[i].type = sync THEN {
    sync: SyncPTR ← Event.Sync[score.event[i]];
    FOR j: CARDINAL IN [0..sync.length) DO
IF (n ← sync.note[j]) = NIL THEN EXIT;
IF n.toc = 0 OR n.duration = 0 THEN LOOP;
min ← MIN[min, n.toc];
noteTime ← n.toc;
IF noteTime-min > 64000 THEN RETURN[min];
ENDLOOP};
    ENDLOOP;
RETURN[min];
END;
-- ************************************************************************
-- making a copy of a portion of the score
-- ************************************************************************
BeamMapPTR: TYPE = LONG POINTER TO BeamMapRec;
BeamMapRec: TYPE = RECORD[length: CARDINAL ← 0,
array: SEQUENCE max: CARDINAL OF RECORD[old, new: BeamPTR ← NIL]];
ChordMapPTR: TYPE = LONG POINTER TO ChordMapRec;
ChordMapRec: TYPE = RECORD[length: CARDINAL ← 0,
array: SEQUENCE max: CARDINAL OF RECORD[old, new: ChordPTR ← NIL]];
NoteMapPTR: TYPE = LONG POINTER TO NoteMapRec;
NoteMapRec: TYPE = RECORD[length: CARDINAL ← 0,
array: SEQUENCE max: CARDINAL OF RECORD[old, new: NotePTR ← NIL]];
Copy: PUBLIC PROCEDURE[score: ScorePTR, time1, time2: Time] RETURNS[copy: ScorePortionPTR] = 
BEGIN ENABLE Piece.Overflow => {IF copy.score = old THEN copy.score ← new; RESUME};
-- copies [time1..time2)
tieMap: NoteMapPTR ← zone.NEW[NoteMapRec[10]];
beamMap: BeamMapPTR ← zone.NEW[BeamMapRec[10]];
chordMap: ChordMapPTR ← zone.NEW[ChordMapRec[10]];
copy ← zone.NEW[ScorePortionRec];
copy.score ← score;
GetScoreState[copy, time1, time2]; 
copy.score ← Piece.New[100, FALSE];
IF score.sheet.voice # noVoice AND score.sheet.display # physical THEN {
start, stop: CARDINAL;
[start, stop] ← SelectMeasures[score, time1, time2];
IF start # stop THEN time1 ← score.event[start].time;
IF stop # start THEN time2 ← score.event[MIN[stop, score.length-1]].time+1;
Selection.AddGreyLine[score, time1, time2]};
FOR i: CARDINAL IN [0..score.length) DO
newEvent: EventPTR;
IF score.event[i].time < time1 THEN LOOP;
IF score.event[i].time >= time2 THEN EXIT;
IF score.sheet.voice # noVoice AND ~Measure[score.event[i]] 
AND score.event[i].type # sync THEN LOOP;
IF Selection.selection.lineSelect AND score.event[i].type # sync THEN 
newEvent ← CopyEvent[score.event[i]]; 
IF score.event[i].type = sync THEN {
n: NotePTR;
sync: SyncPTR ← Event.Sync[score.event[i]];
FOR j: CARDINAL IN [0..sync.length) DO
IF (n ← sync.note[j]) = NIL THEN EXIT;
IF ~Note.InVoice[n, score.sheet.voice] THEN LOOP;
-- IF ~Selection.Includes[n] THEN LOOP;
CopyNote[score, n, newEvent, beamMap, chordMap, tieMap];
ENDLOOP};
UnSave[score.event[i], beamMap, chordMap];
IF newEvent = NIL THEN LOOP;
Event.AddTimes[newEvent, -time1, -copy.toc+500];
copy.score ← Piece.AddEvent[copy.score, newEvent];
ENDLOOP;
FOR i: CARDINAL DECREASING IN [0..copy.score.beamHeap.length) DO
IF copy.score.beamHeap[i].length > 1 THEN LOOP;
Beam.Free[copy.score, copy.score.beamHeap[i]];
ENDLOOP;
FOR i: CARDINAL DECREASING IN [0..copy.score.chordHeap.length) DO
IF copy.score.chordHeap[i].length > 1 THEN LOOP;
Chord.Free[copy.score, copy.score.chordHeap[i]];
ENDLOOP;
zone.FREE[@tieMap];
zone.FREE[@chordMap];
zone.FREE[@beamMap];
RETURN[copy];
END;
CopyEvent: PROC[event: EventPTR] RETURNS[copy: EventPTR] = BEGIN
WITH ev: event SELECT FROM
sync => ERROR;
measure => {
copy ← zone.NEW[EventRec.measure];
Event.Measure[copy]↑ ← ev};
timeSignature => {
copy ← zone.NEW[EventRec.timeSignature];
Event.TimeSignature[copy]↑ ← ev};
keySignature => {
copy ← zone.NEW[EventRec.keySignature];
Event.KeySignature[copy]↑ ← ev};
metrenome => {
copy ← zone.NEW[EventRec.metrenome];
Event.Metrenome[copy]↑ ← ev};
staves => {
copy ← zone.NEW[EventRec.staves];
Event.Staves[copy]↑ ← ev};
ENDCASE => ERROR;
END;
CopyNote: PROCEDURE[score: ScorePTR, old: NotePTR, newEvent: EventPTR, beamMap: BeamMapPTR, chordMap: ChordMapPTR, tieMap: NoteMapPTR] = 
BEGIN
new: NotePTR;
b, oldBeam: BeamPTR;
c, oldChord: ChordPTR;
new ← zone.NEW[NoteRec];
new↑ ← old↑;
oldBeam ← new.beam;
new.beam ← NIL;
IF new.tied THEN {SaveTie[tieMap, old, new]; new.tied ← FALSE};
IF new.tie # NIL THEN {
new.tie ← Find[new.tie];
RemoveTie[tieMap, new.tie];
IF new.tie # NIL THEN new.tie.tied ← TRUE};
oldChord ← Note.FindChord[old];
IF oldChord # NIL THEN BEGIN
c ← Find[oldChord];
IF c = NIL THEN BEGIN 
c ← Chord.New[score, oldChord.max]; 
SaveChord[chordMap, oldChord, c]; 
END;
c.stemUp ← oldChord.stemUp;
c ← Chord.AddNote[score, c, new];
END;
IF newEvent = NIL THEN {
newEvent ← zone.NEW[EventRec.sync[old.sync.max]]; 
newEvent.time ← old.sync.time};
newEvent ← Event.AddNote[score, Event.Sync[newEvent], new];
IF oldBeam = NIL THEN RETURN;
b ← Find[oldBeam];
IF b = NIL THEN 
BEGIN b ← Beam.New[score, oldBeam.max]; 
SaveBeam[beamMap, oldBeam, b]; 
Inline.LongCOPY[oldBeam, SIZE[BeamRec[0]], b]; -- copy all but chords
b.beam ← NIL;
b.sync1 ← b.sync2 ← NIL; 
END;
CopyBeam[score, beamMap, oldBeam, b, old, new];
END;
CopyBeam: PROCEDURE[score: ScorePTR, beamMap: BeamMapPTR, oldBeam, newBeam: BeamPTR, oldNote, newNote: NotePTR] = 
BEGIN
highBeam: BeamPTR;
oldChord, newChord: ChordPTR;
newNote.beam ← newBeam;
FOR i: CARDINAL IN [0..oldBeam.length) DO
oldChord ← Note.FindChord[oldNote];
newChord ← Note.FindChord[newNote];
IF oldBeam.chord[i] = [note[oldNote]] 
THEN newBeam ← Beam.AddItem[score, newBeam, [note[newNote]]];
IF oldBeam.chord[i] = [chord[oldChord]] 
THEN newBeam ← Beam.AddItem[score, newBeam, [chord[newChord]]];
ENDLOOP;
IF oldBeam.beam = NIL OR newBeam.beam # NIL THEN RETURN;
highBeam ← Find[oldBeam.beam];
IF highBeam = NIL THEN BEGIN
highBeam ← Beam.New[score, oldBeam.max]; 
SaveBeam[beamMap, oldBeam.beam, highBeam];
Inline.LongCOPY[oldBeam, SIZE[BeamRec[0]], highBeam]; -- copy all but chords
highBeam.beam ← NIL;
-- highBeam.chord ← ALL[endOfBeam];
highBeam.sync1 ← highBeam.sync2 ← NIL;
END;
highBeam ← Beam.AddItem[score, highBeam, [beam[newBeam]]]; 
END;
SaveBeam: PROCEDURE[map: BeamMapPTR, old, new: BeamPTR] = 
BEGIN
i: CARDINAL;
FOR i IN [0..map.length) DO
IF map[i].old # NIL THEN LOOP;
map[i] ← [old, new];
RETURN;
ENDLOOP;
IF map.length = map.max THEN ERROR;
map[map.length] ← [old, new];
map.length ← map.length + 1;
END;
SaveChord: PROCEDURE[map: ChordMapPTR, old, new: ChordPTR] = 
BEGIN
i: CARDINAL;
FOR i IN [0..map.length) DO
IF map[i].old # NIL THEN LOOP;
map[i] ← [old, new];
RETURN;
ENDLOOP;
IF map.length = map.max THEN ERROR;
map[map.length] ← [old, new];
map.length ← map.length + 1;
END;
SaveTie: PROCEDURE[map: NoteMapPTR, old, new: NotePTR] = 
BEGIN
i: CARDINAL;
FOR i IN [0..map.length) DO
IF map[i].old # NIL THEN LOOP;
map[i] ← [old, new];
RETURN;
ENDLOOP;
IF map.length = map.max THEN ERROR;
map[map.length] ← [old, new];
map.length ← map.length + 1;
END;
RemoveTie: PROCEDURE[map: NoteMapPTR, new: NotePTR] = 
BEGIN
i: CARDINAL;
FOR i IN [0..map.length) DO
IF map[i].new # new THEN LOOP;
map[i] ← [NIL, NIL];
RETURN;
ENDLOOP;
ERROR;
END;
UnSave: PROCEDURE[s: EventPTR, beamMap: BeamMapPTR, chordMap: ChordMapPTR] = 
BEGIN
IF s = NIL THEN RETURN;
FOR i: CARDINAL IN [0..beamMap.length) DO
IF beamMap[i].old # NIL AND beamMap[i].old.sync2 = s 
    THEN beamMap[i] ← [NIL, NIL];
ENDLOOP;
FOR i: CARDINAL IN [0..chordMap.length) DO
IF chordMap[i].old # NIL AND chordMap[i].old.note[0].sync = s 
    THEN chordMap[i] ← [NIL, NIL];
ENDLOOP;
END;
Find: PROCEDURE[old: LONG POINTER] RETURNS[LONG POINTER] = 
BEGIN
i: CARDINAL;
FOR i IN [0..listLength) DO
    IF beamList[i].old = old THEN RETURN[beamList[i].new];
    IF chordList[i].old = old THEN RETURN[chordList[i].new];
    IF tieList[i].old = old THEN RETURN[tieList[i].new];
    ENDLOOP;
RETURN[NIL];
END;
beamList: ARRAY [0..listLength) OF RECORD[old, new: BeamPTR];
chordList: ARRAY [0..listLength) OF RECORD[old, new: ChordPTR];
tieList: ARRAY [0..listLength) OF RECORD[old, new: NotePTR];
listLength: CARDINAL = 10;
-- ********************************************************
-- making score attributes consistent as you cut and paste
-- ********************************************************
GetScoreState: PROCEDURE[ss: ScorePortionPTR, t1, t2: Time] = 
BEGIN
ss.duration ← t2-t1;
IF ss.score.sheet.display = physical
THEN ss.toc ← (t2-t1)*ss.score.sheet.density
ELSE ss.toc ← MinToc[ss.score, t1, t2];
ss.ss1.key ← Score.GetKey[ss.score, t1];
ss.ss2.key ← Score.GetKey[ss.score, t2];
ss.ss1.style ← Score.GetStyle[ss.score, t1];
ss.ss2.style ← Score.GetStyle[ss.score, t2];
ss.ss1.staff ← ss.score.sheet.section[Sheet.FindSection[ss.score.sheet, t1]].staves.staff;
ss.ss2.staff ← ss.score.sheet.section[Sheet.FindSection[ss.score.sheet, t2]].staves.staff;
END;
SetScoreDifferences: PROCEDURE[score: ScorePTR, ss1, ss2: ScoreStatePTR, time: Time] = 
BEGIN
IF ss1.key # ss2.key THEN {
keySig: LONG POINTER TO EventRec.keySignature;
keySig ← zone.NEW[EventRec.keySignature]; 
keySig.time ← time;
keySig.key ← ss2.key;
score ← Piece.AddEvent[score, keySig]};
IF ss1.style # ss2.style THEN {
style: StavesPTR;
style ← zone.NEW[EventRec.staves]; 
style.time ← time;
style.staves ← style;
style.value ← ss2.style;
score ← Piece.AddEvent[score, style]};
FOR i: CARDINAL IN [0..4) DO
staves: StavesPTR;
IF i > 0 AND ss2.staff[i].y = ss2.staff[i-1].y THEN LOOP;
IF ss1.staff[i].pitch = ss2.staff[i].pitch THEN LOOP;
staves ← zone.NEW[EventRec.staves];
staves.time ← time;
staves.value ← i;
staves.staff ← ss2.staff;
SELECT ss2.staff[i].pitch FROM
15, 60 => staves.staves ← octava1;
27 => IF ss1.staff[i].pitch = 48 
THEN staves.staves ← clef 
ELSE staves.staves ← octava2; 
48 => IF ss1.staff[i].pitch = 27 
THEN staves.staves ← clef 
ELSE staves.staves ← octava2;
ENDCASE; 
score ← Piece.AddEvent[score, staves];
ENDLOOP;
END;
END..
Delete: PUBLIC PROCEDURE[begin, end: Time] = 
BEGIN
toc: Time;
n: NotePTR;
j: CARDINAL;
sync: EventPTR;
staves: StavesPTR;
newSheet: BOOLEAN;
key, index: INTEGER;
staff: ARRAY [0..4) OF Staff;
SetDirty[begin, IF voice THEN end ELSE EndOfScore[]];
key ← Score.GetKey[end];
staves ← sheet[Sheet.FindSection[begin]].staves;
-- free sync and invalidate syncs
FOR i: CARDINAL DECREASING IN [0..score.length) DO
IF score.event[i].time >= end THEN LOOP;
IF score.event[i].time < begin THEN EXIT;
IF score.event[i].type = sync THEN FOR j DECREASING IN [0..syncLength) DO
IF (n ← score.event[i].event[j]) = NIL THEN LOOP;
IF voice AND n.voice # selectedVoice THEN LOOP;
-- Piece.-- RemoveNote[n];
Note.Free[@n]; -- takes n out of n.beam, n.chord, etc.
ENDLOOP;
IF voice THEN LOOP;
IF score.event[i].type IN SheetSwitch 
THEN score.event[i].time ← end
ELSE score.event[i].type ← sync; -- deleted by CleanUpEvents
ENDLOOP;
-- invalidate useless sheet switches
newSheet ← FALSE;
staff ← ALL[NIL];
IF ~voice THEN FOR i: CARDINAL DECREASING IN [0..score.length) DO
IF score.event[i].time # end THEN LOOP;
IF score.event[i].type NOT IN SheetSwitch THEN LOOP;
IF score.event[i].type = staves THEN {
IF newSheet THEN score.event[i].type ← sync ELSE newSheet ← TRUE; LOOP};
index ← Index[score.event[i], score.event[i].value]; -- get the normalized index
SELECT score.event[i].type FROM
clef => IF staff[index] # NIL 
THEN score.event[i].type ← sync 
ELSE staff[index] ← score.event[i];
octava1 => IF staff[index] # NIL 
THEN {IF staff[index].type # octava2 THEN Error;
score.event[i].type ← sync;
staff[index].type ← sync;
staff[index] ← NIL}
ELSE staff[index] ← score.event[i];
octava2 => IF staff[index] # NIL AND staff[index].type = octava1 
THEN {score.event[i].type ← sync;
staff[index].type ← sync;
staff[index] ← NIL}
ELSE staff[index] ← score.event[i];
ENDCASE;
ENDLOOP;
-- invalidate duplicate sheet switches
IF ~voice THEN FOR i: CARDINAL IN [0..6) DO
IF staff[i] = NIL THEN LOOP;
IF staves.staff[i].pitch # Event.GetStaff[staff[i], i].pitch THEN LOOP;
staff[i].type ← sync;
ENDLOOP;
Piece.CleanUpEvents[score]; -- frees invalid syncs
-- put back any key signature
IF Score.GetKey[end] # key THEN {
sync ← zone.NEW[EventRec.keySignature];
sync.time ← end;
sync.type ← keySignature;
sync.value ← key;
Piece.AddEvent[score, sync]};
-- slide everything over
toc ← MaxToc[score, 0, begin]-MinToc[end, 1000000];
IF ~voice THEN FOR i: CARDINAL IN [0..score.length) DO
IF score.event[i].time < end THEN LOOP;
Event.AddTimes[score.event[i], begin-end, toc];
ENDLOOP;
Sheet.Reset[];
Selection.AddLine[begin, begin];
END;
Index: PROCEDURE[s: EventPTR, i: CARDINAL] RETURNS[index: INTEGER] = 
  {IF s.type NOT IN SheetSwitch THEN Error;
index ← s.value;
FOR j: CARDINAL DECREASING IN [0..4) DO
IF Event.GetStaff[s, j].y = Event.GetStaff[s, index].y THEN index ← j;
ENDLOOP};
InsertScore: PUBLIC PROCEDURE[new: ScorePTR, size: Time] = 
BEGIN
i, j, k, pLength: CARDINAL ← 0;
maxTime, offset: Time ← 0;
delta: Time ← select2-select1+20;
FOR i IN [0..maxPieceLength) DO 
    IF new.event[i] = NIL THEN BEGIN pLength ← i; EXIT; END;
    ENDLOOP;
FOR i IN [0..pLength) DO maxTime ← MAX[maxTime, new.event[i].time+10]; ENDLOOP;
IF size # 0 THEN maxTime ← size;
IF pLength+score.length >= maxScoreLength THEN ERROR;
DeleteSelection[];
offset ← MaxTime[new, 0, end];
IF show.display = physical THEN offset ← MAX[offset, maxTime*TF];
FOR i DECREASING IN [0..score.length) DO
    IF score.event[i].time <= select1 THEN BEGIN j ← i+1; EXIT; END; 
    Event.AddTimes[score.event[i], maxTime, offset];
    score.event[i+pLength] ← score.event[i];
    ENDLOOP;
offset ← MaxTime[score, 0, select1];
FOR i IN [j..j+pLength) DO
    score.event[i] ← new.event[i-j];
    Event.AddTimes[score.event[i], select1, offset];
    ENDLOOP;
score.length ← score.length + pLength;
SystemDefs.FreeSegment[new];
CleanUpEvents[];
min ← select1;
max ← EndOfScore[]+MAX[delta, maxTime];
END;
Replace: PUBLIC PROCEDURE[score, score2: ScorePTR, delete1, delete2, copy1, copy2: Time] = 
BEGIN ENABLE Piece.Overflow => {
	IF score = old THEN score ← new;
	IF score2 = old THEN score2 ← new};
copy: ScorePTR;
cs1, cs2, ds1, ds2: ScoreState;
IF score2 # NIL THEN {
	GetScoreState[score, @ds1, MAX[delete1-1, 0]];
	GetScoreState[score, @ds2, delete2];
	GetScoreState[score2, @cs1, MAX[copy1-1, 0]];
	GetScoreState[score2, @cs2, copy2];
	copy ← Copy[score2, copy1, copy2]};
Delete[score, delete1, delete2];
IF copy = NIL THEN RETURN;
IF score.sheet.voice # noVoice 
	THEN Piece.Merge[score, copy, delete1, delete2]
	ELSE {
		Insert[score, copy, delete1];
		SetScoreDifferences[score, @ds1, @cs1, delete1];
		SetScoreDifferences[score, @cs2, @ds2, delete1+copy2-copy1];
		Sheet.Reset[score]};
END;