<> <> <> <> <> DIRECTORY Chord USING [Free], Event USING [AddNote, AddTimes, Free], MusicDefs, Note USING [Free, InVoice], Piece USING [AddEvent, CleanUpEvents, Free, NearestEvent], Real USING [Fix], Score USING [GetKey, GetStyle], Sheet USING [FindSection, Reset], Selection USING [AddLine, selection], Voice USING [Correct]; PieceImplB: CEDAR PROGRAM IMPORTS Chord, Event, MusicDefs, Note, Piece, Real, Score, Sheet, Selection, Voice EXPORTS Piece = BEGIN OPEN MusicDefs; <<****************************************************************************>> <
> <<****************************************************************************>> Merge: PUBLIC PROC[score, new: ScorePTR, begin, end: Time] = { < IF score = old THEN score _ new;>> l: REAL = 1; scale: REAL; sBegin: Time; sync: BOOL; 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}; <> [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]; <> 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]; <> 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]; <> 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}; <> 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 <> 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; <> 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]; }; SelectMeasures: PROC[score: ScorePTR, begin, end: Time] RETURNS[start, stop: CARDINAL] = { <> 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; <> 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; }; MergeSection: PROC[score, new: ScorePTR, begin: Time, start, stop: CARDINAL] = { <> FOR i: CARDINAL IN [start..stop) DO new.event[i].time _ new.event[i].time+begin; ENDLOOP; FOR i: CARDINAL IN [start..stop) DO newEvent: EventPTR _ new.event[i]; WITH newEvent SELECT FROM newSync: SyncPTR => { nearest: EventPTR ~ score.event[Piece.NearestEvent[score, newSync.time, TRUE]]; WITH nearest SELECT FROM oldSync: SyncPTR => IF ABS[oldSync.time-newSync.time]<=1 THEN { FOR j: NAT DECREASING IN[0..newSync.length) DO Event.AddNote[score, oldSync, newSync.note[j]]; ENDLOOP; newEvent _ NIL; }; ENDCASE; }; staves: StavesPTR => IF staves.staves=style THEN newEvent _ NIL; ENDCASE => newEvent _ NIL; IF newEvent#NIL THEN Piece.AddEvent[score, newEvent]; new.event[i] _ NIL; ENDLOOP; }; Replace: PUBLIC PROC[score: ScorePTR, new: ScorePortionPTR, delete1, delete2: Time] = { < IF score = old THEN score _ new;>> <> portion: ScorePortionPTR ~ NEW[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]; <> <> 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]; <> }; Sheet.Reset[score]; Selection.AddLine[score, delete1, delete1]; }; DeleteSection: PUBLIC PROC[score: ScorePTR, delete1, delete2, toc: Time] = { voice: BOOL _ score.sheet.voice # noVoice; SetDirty[score, delete1, IF voice THEN delete2 ELSE LAST[Time]]; <> FOR i: CARDINAL DECREASING IN [0..score.length) DO event: EventPTR ~ score.event[i]; IF event.time >= delete1 THEN LOOP; IF event.time < delete2 THEN EXIT; WITH event SELECT FROM sync: SyncPTR => { FOR j: NAT 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; }; ENDCASE; IF ~voice AND i # 0 THEN Event.Free[score, event]; 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]; }; InsertSection: PROC[score, new: ScorePTR, begin, duration, toc: Time] = { <> start: CARDINAL _ 0; length: CARDINAL = new.length; <> 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; <> 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]; WITH score.event[i] SELECT FROM sync: SyncPTR => Event.AddTimes[sync, begin, toc]; ENDCASE; 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]]; }; Size: PROC[score: ScorePTR, length: CARDINAL] RETURNS[size, toc: Time _ 0] = { 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]; WITH score.event[i] SELECT FROM sync: SyncPTR => { FOR j: NAT IN[0..sync.length) DO n: NotePTR ~ sync.note[j]; IF n=NIL THEN EXIT; IF n.toc = 0 THEN LOOP; toc _ MAX[toc, n.toc+n.duration]; IF score.sheet.max-n.toc > 64000 THEN EXIT; ENDLOOP; }; ENDCASE; 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; }; MaxToc: PUBLIC PROC[score: ScorePTR, time1, time2: Time, duration: BOOL] RETURNS[Time] = { 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 event: EventPTR ~ score.event[i]; IF event.time >= time2 THEN LOOP; IF event.time <= time1 THEN EXIT; WITH event SELECT FROM sync: SyncPTR => { FOR j: NAT IN[0..sync.length) DO n: NotePTR ~ sync.note[j]; IF n = 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; }; ENDCASE; ENDLOOP; RETURN[max]; }; end: Time = 10000000; MinToc: PROC[score: ScorePTR, time1, time2: Time] RETURNS[Time] = { min: Time _ end; noteTime: Time; IF score.sheet.display = physical AND time1 # 0 THEN min _ time1*score.sheet.density; FOR i: CARDINAL IN [0..score.length) DO event: EventPTR ~ score.event[i]; IF event.time < time1 THEN LOOP; IF event.time > time2 THEN EXIT; WITH event SELECT FROM sync: SyncPTR => { FOR j: NAT IN[0..sync.length) DO n: NotePTR ~ sync.note[j]; IF n = 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; }; ENDCASE; ENDLOOP; RETURN[min]; }; <<>> <<********************************************************>> <> <<********************************************************>> GetScoreState: PROC[ss: ScorePortionPTR, t1, t2: Time] = { 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; }; SetScoreDifferences: PROC[score: ScorePTR, ss1, ss2: ScoreStateRec, time: Time] = { IF ss1.key # ss2.key THEN { keySig: KeySignaturePTR ~ NEW[EventRec[keySignature]]; keySig.time _ time; keySig.key _ ss2.key; Piece.AddEvent[score, keySig]; }; IF ss1.style # ss2.style THEN { style: StavesPTR ~ NEW[EventRec[staves]]; style.time _ time; style.staves _ style; style.value _ ss2.style; 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 _ 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; Piece.AddEvent[score, staves]; ENDLOOP; }; END. <<************************************************************************>> <> <<************************************************************************>> BeamMapPTR: TYPE = REF BeamMapRec; BeamMapRec: TYPE = RECORD[length: CARDINAL _ 0, array: SEQUENCE max: CARDINAL OF RECORD[old, new: BeamPTR _ NIL]]; ChordMapPTR: TYPE = REF ChordMapRec; ChordMapRec: TYPE = RECORD[length: CARDINAL _ 0, array: SEQUENCE max: CARDINAL OF RECORD[old, new: ChordPTR _ NIL]]; NoteMapPTR: TYPE = REF NoteMapRec; NoteMapRec: TYPE = RECORD[length: CARDINAL _ 0, array: SEQUENCE max: CARDINAL OF RECORD[old, new: NotePTR _ NIL]]; Copy: PUBLIC PROC[score: ScorePTR, time1, time2: Time] RETURNS[copy: ScorePortionPTR] = { < {IF copy.score = old THEN copy.score _ new; RESUME};>> <> 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; <> 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]; }; CopyEvent: PROC[event: EventPTR] RETURNS[copy: EventPTR] = { 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; }; CopyNote: PROC[score: ScorePTR, old: NotePTR, newEvent: EventPTR, beamMap: BeamMapPTR, chordMap: ChordMapPTR, tieMap: NoteMapPTR] = { 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 { c _ Find[oldChord]; IF c = NIL THEN { c _ Chord.New[score, oldChord.max]; SaveChord[chordMap, oldChord, c]; }; c.stemUp _ oldChord.stemUp; c _ Chord.AddNote[score, c, new]; }; 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 { 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; }; CopyBeam[score, beamMap, oldBeam, b, old, new]; }; CopyBeam: PROC[score: ScorePTR, beamMap: BeamMapPTR, oldBeam, newBeam: BeamPTR, oldNote, newNote: NotePTR] = { 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 { 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.sync1 _ highBeam.sync2 _ NIL; }; highBeam _ Beam.AddItem[score, highBeam, [beam[newBeam]]]; }; SaveBeam: PROC[map: BeamMapPTR, old, new: BeamPTR] = { 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; }; SaveChord: PROC[map: ChordMapPTR, old, new: ChordPTR] = { 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; }; SaveTie: PROC[map: NoteMapPTR, old, new: NotePTR] = { 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; }; RemoveTie: PROC[map: NoteMapPTR, new: NotePTR] = { i: CARDINAL; FOR i IN [0..map.length) DO IF map[i].new # new THEN LOOP; map[i] _ [NIL, NIL]; RETURN; ENDLOOP; ERROR; }; UnSave: PROC[s: EventPTR, beamMap: BeamMapPTR, chordMap: ChordMapPTR] = { 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; }; Find: PROC[old: LONG POINTER] RETURNS[LONG POINTER] = { 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]; }; listLength: CARDINAL = 10; 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]; <<************************************************************************>> Delete: PUBLIC PROC[begin, end: Time] = { toc: Time; n: NotePTR; j: CARDINAL; sync: EventPTR; staves: StavesPTR; newSheet: BOOL; 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; <> 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; <> 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; <> 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 <> IF Score.GetKey[end] # key THEN { sync _ zone.NEW[EventRec.keySignature]; sync.time _ end; sync.type _ keySignature; sync.value _ key; Piece.AddEvent[score, sync]}; <> 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]; }; Index: PROC[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 PROC[new: ScorePTR, size: Time] = { 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 { pLength _ i; EXIT; }; 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 { j _ i+1; EXIT; }; 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]; }; Replace: PUBLIC PROC[score, score2: ScorePTR, delete1, delete2, copy1, copy2: Time] = { < {>> <> 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]}; };