--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].timeend 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].time10 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].timetime2 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=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.. e6(0,3648)(1,4288)(2,4928)\873i20I81b5B4918b7B517b6B1212b11B556b6B1513b6B1216b5B 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 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=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; (1792)\1b6B2725b11B