--Author: John Maxwell
--last modified: December 15, 1981 8:13 AM

DIRECTORY
Beam USING [AddBeam,AddChord,AddNote,Remove],
Chord USING [AddNote,RemoveNote],
MusicDefs,
Note USING [FindChord,GetBackTie],
Piece USING [AddSync, CleanUpSyncs, Insert, Length, Merge, NearestSync],
Real USING [Fix],
Score USING [GetKey],
Sheet USING [FindSection,Reset],
Selection USING [AddLine, AddGreyLine],
Sync USING [AddNote,AddTimes,GetStaff,RemoveNote],
Utility USING [FreeBeam, FreeChord, FreeNote, FreePiece, FreeSync, NewBeam, NewChord, NewNote, NewPiece, NewSync],
Voice USING [Correct];

PieceImplB: PROGRAM
IMPORTS Beam, Chord, MusicDefs, Note, Piece, Real, Score, Sheet, Selection, Sync, Utility, Voice
EXPORTS Piece =

BEGIN
OPEN MusicDefs;

Error:SIGNAL;

--****************************************************************************
--
section manipulation
--****************************************************************************

Merge:PUBLIC PROCEDURE[begin,end:Time,p:PiecePTR] =
BEGIN
l:REAL=1;
scale:REAL;
sBegin:Time;
notes: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 = Piece.Length[p];
SetDirty[begin,end];
IF length=0 THEN RETURN;
IF show.display=physical THEN {
MergeSection[begin,p,0,length];
Utility.FreePiece[@p];
RETURN};
-- where does the score start and stop?
[start,stop] ← SelectMeasures[begin,end];
IF start#stop THEN begin←score[start].time;
IF start#stop THEN end←score[MIN[stop,scoreLength-1]].time+1;
Selection.AddLine[begin,end];
-- how are the measures in p distributed?
notes ← FALSE;
FOR i:CARDINAL IN [0..length) DO
IF p[i].type=notes THEN notes←TRUE;
IF NOT Measure[p[i].type] THEN LOOP;
IF measuresP=-1 THEN {
pmFirst ← p[i].time-p[0].time;
IF notes THEN pmFirst ← MAX[pmFirst,tolerance+1]};
notes ← FALSE;
pmLast ← p[length-1].time-p[i].time;
measuresP ← measuresP + 1;
ENDLOOP;
IF notes THEN pmLast ← MAX[pmLast,tolerance+1];
-- how are the measures in the score distributed?
notes ← FALSE;
FOR i:CARDINAL IN [start..stop) DO
IF NOT Measure[score[i].type] THEN LOOP;
IF measuresS=-1 THEN {
smFirst ← score[i].time-score[start].time;
IF notes THEN smFirst ← MAX[smFirst,tolerance+1]};
notes ← FALSE;
smLast ← score[MIN[stop,scoreLength-1]].time-score[i].time;
measuresS ← measuresS + 1;
ENDLOOP;
IF notes 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[select1+smFirst+1,select2];
IF smLast<=tolerance THEN Selection.AddLine[select1,select2-smLast-1];
IF measuresS<1 THEN measuresS←1;
IF measuresP<1 THEN measuresP←1;
IF measuresS#0 AND measuresS#measuresP THEN {
flash←TRUE;
Utility.FreePiece[@p];
RETURN};
-- merge p into the score measure by measure
pEnd ← p[length-1].time;
pStart ← length; sStart ← stop;
IF Measure[p[length-1].type] 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[p[j].type] 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[j].type] 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 p’s measure and merge it into the score
IF i=0 THEN sBegin ← begin ELSE sBegin ← score[sStart].time;
IF i#measuresP-1 THEN end ← score[sStop].time;
pBegin ← (IF pStart=0 THEN 0 ELSE p[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
p[j].time ← Real.Fix[scale*(p[j].time-pEnd)];
ENDLOOP;
MergeSection[sBegin,p,pStart,pStop];
ENDLOOP;
Utility.FreePiece[@p];
Voice.Correct[select1,select2];
Sheet.Reset[];
END;

SelectMeasures:PROC[begin,end:Time] RETURNS[start,stop:CARDINAL] =
BEGIN
-- find the start
start←scoreLength; stop←0;
FOR i:CARDINAL DECREASING IN [0..scoreLength) DO
IF score[i].time<begin AND Measure[score[start].type] AND start#0 THEN EXIT;
IF score[i].time<begin AND score[i].type=notes THEN EXIT;
IF score[i].time<begin-40 THEN EXIT;
IF Measure[score[i].type] OR score[i].type=notes THEN start←i;
ENDLOOP;
-- find the stop
FOR i:CARDINAL IN [0..scoreLength] DO
IF i=scoreLength THEN {stop←i; EXIT};
IF score[i].time>end AND Measure[score[stop].type] AND stop#0 THEN EXIT;
IF score[i].time>end AND score[i].type=notes THEN EXIT;
IF score[i].time>end+40 THEN EXIT;
IF Measure[score[i].type] OR score[i].type=notes THEN stop←i;
ENDLOOP;
IF start=scoreLength THEN start←stop;
IF stop=0 THEN stop←start;
END;

MergeSection:PROCEDURE[begin:Time,p:PiecePTR,start,stop:CARDINAL] =
BEGIN -- start and stop are indices into p, begin is the time where it goes in score
s:SyncPTR;
FOR i:CARDINAL IN [start..stop) DO
p[i].time ← p[i].time+begin;
ENDLOOP;
FOR i:CARDINAL IN [start..stop) DO
IF NOT (p[i].type=notes OR (p[i].type IN SheetSwitch AND p[i].type#staves)) THEN {Utility.FreeSync[@p[i]]; LOOP};
s ← score[Piece.NearestSync[score,p[i].time,TRUE]];
IF s=NIL OR ABS[s.time-p[i].time]>1 OR p[i].type#notes THEN
{Piece.AddSync[score,p[i]]; p[i]←NIL; LOOP};
FOR j:CARDINAL DECREASING IN [0..syncLength) DO
IF p[i].event[j]=NIL THEN LOOP;
Sync.AddNote[s,p[i].event[j]];
ENDLOOP;
Utility.FreeSync[@p[i]];
ENDLOOP;
END;

Replace:PUBLIC PROCEDURE[delete1,delete2,copy1,copy2:Time] =
BEGIN
copy:PiecePTR;
cs1,cs2,ds1,ds2:ScoreState;
GetScoreState[@cs1,MAX[copy1-1,0]];
GetScoreState[@cs2,copy2];
GetScoreState[@ds1,MAX[delete1-1,0]];
GetScoreState[@ds2,delete2];
copy ← Copy[copy1,copy2];
Delete[delete1,delete2];
IF copy=NIL THEN RETURN;
IF voice
THEN Piece.Merge[delete1,delete2,copy]
ELSE {
Piece.Insert[delete1,copy];
SetScoreDifferences[@ds1,@cs1,delete1];
SetScoreDifferences[@cs2,@ds2,delete1+copy2-copy1];
Sheet.Reset[]};
END;

Delete:PUBLIC PROCEDURE[begin,end:Time] =
BEGIN -- deletes [begin..end),
toc:Time;
n:NotePTR;
j:CARDINAL;
endState:ScoreState;
beginState:ScoreState;
SetDirty[begin,IF voice THEN end ELSE EndOfScore[]];
IF ~voice THEN {
GetScoreState[@beginState,begin-1];
GetScoreState[@endState,end]};
--free notes and invalidate syncs
FOR i:CARDINAL DECREASING IN [0..scoreLength) DO
IF score[i].time>=end THEN LOOP;
IF score[i].time<begin THEN EXIT;
IF score[i].type=notes THEN FOR j DECREASING IN [0..syncLength) DO
IF (n←score[i].event[j])=NIL THEN LOOP;
IF voice AND n.voice#selectedVoice THEN LOOP;
--Piece.--RemoveNote[n];
Utility.FreeNote[@n]; -- takes n out of n.beam, n.chord, etc.
ENDLOOP;
-- everything else is actually deleted by CleanUpSyncs
IF ~voice AND i#0 THEN score[i].type ← notes;
ENDLOOP;
Piece.CleanUpSyncs[score];
IF voice THEN RETURN;
SetScoreDifferences[@beginState,@endState,begin];
-- slide everything over
toc← MaxToc[score,0,begin,FALSE]-MinToc[end,1000000];
IF show.display=physical THEN toc ← (begin-end)*TF;
FOR i:CARDINAL IN [0..scoreLength) DO
IF score[i].time<end THEN LOOP;
Sync.AddTimes[score[i],begin-end,toc];
ENDLOOP;
Sheet.Reset[];
Selection.AddLine[begin,begin];
END;

RemoveNote
:PUBLIC PROCEDURE[n:NotePTR] =
BEGIN
IF n.tied THEN Note.GetBackTie[n].tie←NIL;
IF n.tie#NIL THEN n.tie.tied←FALSE;
n.tied ← FALSE; n.tie ← NIL;
IF n.chord#NIL THEN Chord.RemoveNote[n.chord,n];
IF n.beam#NIL THEN Beam.Remove[n.beam,n,NIL,NIL];
IF n.sync#NIL THEN Sync.RemoveNote[n.sync,n];
n.sync ← NIL;
END;

Index:PROCEDURE[s:SyncPTR,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 Sync.GetStaff[s,j].y=Sync.GetStaff[s,index].y THEN index ← j;
ENDLOOP};


Insert:PUBLIC PROCEDURE[begin:Time,new:PiecePTR] =
BEGIN -- anything at begin ends up after new
size,toc:Time;
start:CARDINAL←0;
length:CARDINAL = Piece.Length[new];
--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..scoreLength) DO
IF score[i].time<begin THEN {start←i+1; EXIT};
Sync.AddTimes[score[i],size,toc];
score[i+length]←score[i];
ENDLOOP;
--insert the new score
IF show.display=physical
THEN toc←begin*TF
ELSE toc←MaxToc[score,0,begin,TRUE];
FOR i:CARDINAL IN [start..start+length) DO
score[i] ← new[i-start];
Sync.AddTimes[score[i],begin,toc];
new[i-start] ← NIL; -- so FreePiece doesn’t free the syncs
ENDLOOP;
scoreLength ← scoreLength + length;
Piece.CleanUpSyncs[score];
Utility.FreePiece[@new];
Sheet.Reset[];
IF lineSelect THEN Selection.AddLine[begin,begin+size];
SetDirty[begin,EndOfScore[]];
END;

Size:PROCEDURE[p:PiecePTR,length:CARDINAL] RETURNS[size,toc:Time←0] =
BEGIN
n:NotePTR;
noteTime:Time;
grey:Time=greySelect2-greySelect1;
FOR i:CARDINAL IN [(IF length>10 THEN length-10 ELSE 0)..length) DO
size ← MAX[size,p[i].time-p[0].time];
FOR j:CARDINAL IN [0..syncLength) DO
IF (n←p[i].event[j])=NIL THEN EXIT;
IF n.toc=0 THEN LOOP;
toc ← MAX[toc,n.toc+n.duration];
noteTime ← n.toc;
IF 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 show.display=physical THEN toc←size*TF;
END;

MaxToc:PUBLIC PROCEDURE[piece:PiecePTR,time1,time2:Time,duration:BOOLEAN] RETURNS[Time]=
BEGIN
n:NotePTR;
max:Time←0;
i,j:CARDINAL;
noteTime:Time←end;
IF piece=score AND show.display=physical THEN RETURN[time2*TF];
FOR i DECREASING IN [0..Piece.Length[piece]) DO
IF piece[i]=NIL THEN LOOP;
IF piece[i].time>=time2 THEN LOOP;
IF piece[i].time<=time1 THEN EXIT;
FOR j IN [0..syncLength) DO
IF (n←piece[i].event[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[time1,time2:Time] RETURNS[Time]=
BEGIN
min:Time←end;
noteTime:Time;
n:NotePTR;
i,j:CARDINAL;
IF show.display=physical AND time1#0 THEN min←time1*TF;
FOR i IN [0..scoreLength) DO
IF score[i]=NIL THEN LOOP;
IF score[i].time<time1 THEN LOOP;
IF score[i].time>time2 THEN EXIT;
FOR j IN [0..syncLength) DO
IF (n←score[i].event[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;

Copy
:PUBLIC PROCEDURE[time1,time2:Time] RETURNS[PiecePTR]=
BEGIN -- copies [time1..time2)
offset:Time;
n:NotePTR;
b:BeamPTR;
c:ChordPTR;
i,j:CARDINAL;
piece:PiecePTR;
piece ← Utility.NewPiece[];
beamList ← ALL[[NIL,NIL]];
chordList ← ALL[[NIL,NIL]];
tieList ← ALL[[NIL,NIL]];
offset ← MinToc[time1,time2];
IF voice AND show.display#physical THEN {
start,stop:CARDINAL;
[start,stop] ← SelectMeasures[time1,time2];
IF start#stop THEN time1←score[start].time;
IF stop#start THEN time2←score[MIN[stop,scoreLength-1]].time+1;
Selection.AddGreyLine[time1,time2]};
FOR i IN [0..scoreLength) DO
IF score[i].time<time1 THEN LOOP;
IF score[i].time>=time2 THEN EXIT;
IF voice AND ~Measure[score[i].type] AND score[i].type#notes THEN LOOP;
IF lineSelect AND score[i].type#notes THEN {
newSync←Utility.NewSync[];
newSync↑←score[i]↑};
IF score[i].type=notes THEN FOR j IN [0..syncLength) DO
IF (n←score[i].event[j])=NIL THEN EXIT;
IF voice AND n.voice#selectedVoice THEN LOOP;
--IF ~Selection.Includes[n] THEN LOOP;
CopyNote[n];
ENDLOOP;
UnSave[score[i]];
IF newSync=NIL THEN LOOP;
Sync.AddTimes[newSync,-time1,-offset+500];
Piece.AddSync[piece,newSync];
newSync ← NIL;
ENDLOOP;
FOR i DECREASING IN [0..beamHeapLength) DO
IF beamHeap[i].chord[1]#endOfBeam THEN LOOP;
b ← beamHeap[i];
Utility.FreeBeam[@b];
ENDLOOP;
FOR i DECREASING IN [0..chordHeapLength) DO
IF chordHeap[i].note[1]#NIL THEN LOOP;
c ← chordHeap[i];
Utility.FreeChord[@c];
ENDLOOP;
RETURN[piece];
END;

newSync:SyncPTR←NIL;

CopyNote:PROCEDURE[old:NotePTR] =
BEGIN
new:NotePTR;
b,oldBeam:BeamPTR;
c,oldChord:ChordPTR;
new ← Utility.NewNote[];
new↑ ← old↑;
oldBeam ← new.beam;
new.beam ← NIL;
IF new.tied THEN {SaveTie[old,new]; new.tied←FALSE};
IF new.tie#NIL THEN {
new.tie ← Find[new.tie];
RemoveTie[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 ← Utility.NewChord[]; SaveChord[oldChord,c]; END;
c.stemUp ← oldChord.stemUp;
Chord.AddNote[c,new];
END;
IF newSync=NIL THEN {
newSync←Utility.NewSync[];
newSync.time ← old.sync.time;
newSync.type ← notes};
Sync.AddNote[newSync,new];
IF oldBeam=NIL THEN RETURN;
b ← Find[oldBeam];
IF b=NIL THEN
BEGIN b ← Utility.NewBeam[];
SaveBeam[oldBeam,b];
b↑ ← oldBeam↑; b.beam←NIL;
b.chord ← ALL[endOfBeam];
b.sync1 ← b.sync2 ← NIL;
END;
CopyBeam[oldBeam,b,old,new];
END;

CopyBeam:PROCEDURE[oldBeam,newBeam:BeamPTR,oldNote,newNote:NotePTR] =
BEGIN
i:CARDINAL;
highBeam:BeamPTR;
oldChord,newChord:ChordPTR;
newNote.beam ← newBeam;
FOR i IN [0..beamLength) DO
IF oldBeam.chord[i] = endOfBeam THEN EXIT;
oldChord ← Note.FindChord[oldNote];
newChord ← Note.FindChord[newNote];
WITH ev:oldBeam.chord[i] SELECT FROM
note => IF ev=[note[oldNote]] THEN Beam.AddNote[newBeam,newNote];
chord=> IF ev=[chord[oldChord]] THEN Beam.AddChord[newBeam,newChord];
ENDCASE;
ENDLOOP;
IF oldBeam.beam=NIL OR newBeam.beam#NIL THEN RETURN;
highBeam ← Find[oldBeam.beam];
IF highBeam=NIL THEN BEGIN
highBeam←Utility.NewBeam[];
SaveBeam[oldBeam.beam,highBeam];
highBeam↑ ← oldBeam.beam↑;
highBeam.beam←NIL;
highBeam.chord ← ALL[endOfBeam];
highBeam.sync1 ← highBeam.sync2 ← NIL;
END;
Beam.AddBeam[highBeam,newBeam];
END;

SaveBeam:PROCEDURE[old,new:BeamPTR] =
BEGIN
i:CARDINAL;
FOR i IN [0..listLength) DO
IF beamList[i].old#NIL THEN LOOP;
beamList[i] ← [old,new];
RETURN;
ENDLOOP;
Error;
END;

SaveChord:PROCEDURE[old,new:ChordPTR] =
BEGIN
i:CARDINAL;
FOR i IN [0..listLength) DO
IF chordList[i].old#NIL THEN LOOP;
chordList[i] ← [old,new];
RETURN;
ENDLOOP;
Error;
END;

SaveTie:PROCEDURE[old,new:NotePTR] =
BEGIN
i:CARDINAL;
FOR i IN [0..listLength) DO
IF tieList[i].old#NIL THEN LOOP;
tieList[i] ← [old,new];
RETURN;
ENDLOOP;
Error;
END;

RemoveTie:PROCEDURE[new:NotePTR] =
BEGIN
i:CARDINAL;
FOR i IN [0..listLength) DO
IF tieList[i].new#new THEN LOOP;
tieList[i]←[NIL,NIL];
RETURN;
ENDLOOP;
Error;
END;

UnSave:PROCEDURE[s:SyncPTR] =
BEGIN
i:CARDINAL;
IF s=NIL THEN RETURN;
FOR i IN [0..listLength) DO
IF beamList[i].old#NIL AND beamList[i].old.sync2=s
THEN beamList[i] ← [NIL,NIL];
IF chordList[i].old#NIL AND chordList[i].old.note[0].sync=s
THEN chordList[i] ← [NIL,NIL];
ENDLOOP;
END;

Find:PROCEDURE[old:UnspecifiedPTR] RETURNS[UnspecifiedPTR] =
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
--********************************************************

ScoreStatePTR:TYPE = POINTER TO ScoreState;
ScoreState:TYPE = RECORD[key:INTEGER,staff:ARRAY [0..4) OF Staff];

GetScoreState:PROCEDURE[ss:ScoreStatePTR,t:Time] =
BEGIN
ss.key ← Score.GetKey[t];
ss.staff ← sheet[Sheet.FindSection[t]].staves.staff;
END;

SetScoreDifferences:PROCEDURE[ss1,ss2:ScoreStatePTR,t:Time] =
BEGIN
sync:SyncPTR;
staves:StavesPTR;
IF ss1.key#ss2.key THEN {
sync ← Utility.NewSync[];
sync.time ← t;
sync.type ← keySignature;
sync.value ← ss2.key;
Piece.AddSync[score,sync]};
FOR i:CARDINAL IN [0..4) DO
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;
sync ← Utility.NewSync[];
sync.time ← t;
sync.value ← i;
staves ← LOOPHOLE[@sync.event];
staves.staff ← ss2.staff;
SELECT ss2.staff[i].pitch FROM
15,60 => sync.type ← octava1;
27 => IF ss1.staff[i].pitch=48
THEN sync.type ← clef
ELSE sync.type ← octava2;
48 => IF ss1.staff[i].pitch=27
THEN sync.type ← clef
ELSE sync.type ← octava2;
ENDCASE;
Piece.AddSync[score,sync];
ENDLOOP;
END;

END..


Delete:PUBLIC PROCEDURE[begin,end:Time] =
BEGIN
toc:Time;
n:NotePTR;
j:CARDINAL;
sync:SyncPTR;
staves:StavesPTR;
newSheet:BOOLEAN;
key,index:INTEGER;
staff:ARRAY [0..6) OF SyncPTR;
SetDirty[begin,IF voice THEN end ELSE EndOfScore[]];
key ← Score.GetKey[end];
staves ← sheet[Sheet.FindSection[begin]].staves;
--free notes and invalidate syncs
FOR i:CARDINAL DECREASING IN [0..scoreLength) DO
IF score[i].time>=end THEN LOOP;
IF score[i].time<begin THEN EXIT;
IF score[i].type=notes THEN FOR j DECREASING IN [0..syncLength) DO
IF (n←score[i].event[j])=NIL THEN LOOP;
IF voice AND n.voice#selectedVoice THEN LOOP;
--Piece.--RemoveNote[n];
Utility.FreeNote[@n]; -- takes n out of n.beam, n.chord, etc.
ENDLOOP;
IF voice THEN LOOP;
IF score[i].type IN SheetSwitch
THEN score[i].time ← end
ELSE score[i].type ← notes; -- deleted by CleanUpSyncs
ENDLOOP;
-- invalidate useless sheet switches
newSheet ← FALSE;
staff ← ALL[NIL];
IF ~voice THEN FOR i:CARDINAL DECREASING IN [0..scoreLength) DO
IF score[i].time#end THEN LOOP;
IF score[i].type NOT IN SheetSwitch THEN LOOP;
IF score[i].type = staves THEN {
IF newSheet THEN score[i].type←notes ELSE newSheet←TRUE; LOOP};
index ← Index[score[i],score[i].value]; -- get the normalized index
SELECT score[i].type FROM
clef => IF staff[index]#NIL
THEN score[i].type←notes
ELSE staff[index] ← score[i];
octava1 => IF staff[index]#NIL
THEN {IF staff[index].type#octava2 THEN Error;
score[i].type ← notes;
staff[index].type ← notes;
staff[index] ← NIL}
ELSE staff[index] ← score[i];
octava2 => IF staff[index]#NIL AND staff[index].type=octava1
THEN {score[i].type ← notes;
staff[index].type ← notes;
staff[index] ← NIL}
ELSE staff[index] ← score[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#Sync.GetStaff[staff[i],i].pitch THEN LOOP;
staff[i].type ← notes;
ENDLOOP;
Piece.CleanUpSyncs[score]; -- frees invalid syncs
-- put back any key signature
IF Score.GetKey[end]#key THEN {
sync ← Utility.NewSync[];
sync.time ← end;
sync.type ← keySignature;
sync.value ← key;
Piece.AddSync[score,sync]};
-- slide everything over
toc← MaxToc[score,0,begin]-MinToc[end,1000000];
IF ~voice THEN FOR i:CARDINAL IN [0..scoreLength) DO
IF score[i].time<end THEN LOOP;
Sync.AddTimes[score[i],begin-end,toc];
ENDLOOP;
Sheet.Reset[];
Selection.AddLine[begin,begin];
END;

Index:PROCEDURE[s:SyncPTR,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 Sync.GetStaff[s,j].y=Sync.GetStaff[s,index].y THEN index ← j;
ENDLOOP};
InsertScore:PUBLIC PROCEDURE[new:PiecePTR,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[i]=NIL THEN BEGIN pLength←i; EXIT; END;
ENDLOOP;
FOR i IN [0..pLength) DO maxTime ← MAX[maxTime,new[i].time+10]; ENDLOOP;
IF size#0 THEN maxTime ← size;
IF pLength+scoreLength>=maxScoreLength THEN ERROR;
DeleteSelection[];
offset ← MaxTime[new,0,end];
IF show.display=physical THEN offset← MAX[offset,maxTime*TF];
FOR i DECREASING IN [0..scoreLength) DO
IF score[i].time<=select1 THEN BEGIN j←i+1; EXIT; END;
Sync.AddTimes[score[i],maxTime,offset];
score[i+pLength]←score[i];
ENDLOOP;
offset ← MaxTime[score,0,select1];
FOR i IN [j..j+pLength) DO
score[i] ← new[i-j];
Sync.AddTimes[score[i],select1,offset];
ENDLOOP;
scoreLength ← scoreLength + pLength;
SystemDefs.FreeSegment[new];
CleanUpSyncs[];
min ← select1;
max ← EndOfScore[]+MAX[delta,maxTime];
END;