module ZMidi.Score.Utilities (
TickMap
, buildTickMap
, gcIOId
, isTempoChange
, isTimeSig
, isKeyChange
, isNoteEvent
, nrOfNotes
, toIOIs
, toOnsets
, toMidiNr
, toPitch
, getPitch
, getInterval
, changePitch
, pitchClass
, hasTimeSigs
, updateTimeSig
, removeLabels
, hasNotes
) where
import ZMidi.Score.Internal
import ZMidi.Score.Datatypes
import ZMidi.Core ( MidiFile (..), MidiEvent (..)
, MidiVoiceEvent (..), MidiMetaEvent (..)
, MidiMessage, MidiTrack (..)
)
import Control.Monad.State ( State, modify, execState )
import Control.Arrow ( first, (***) )
import Data.Word ( Word8 )
import Data.Maybe ( isJust )
import Data.List ( find, sort )
import qualified Data.List.Ordered as Sort ( nub )
import Data.Foldable ( foldrM )
import Data.IntMap.Lazy ( insertWith, IntMap, keys )
import qualified Data.IntMap.Lazy as M ( empty )
type TickMap = IntMap Time
gcIOId :: TickMap -> Time
gcIOId tm = case keys $ tm of
[] -> 0
l -> Time . foldr1 gcd $ l
buildTickMap :: [Voice] -> TickMap
buildTickMap = foldr oneVoice M.empty where
oneVoice :: Voice -> TickMap -> TickMap
oneVoice [] tm = tm
oneVoice vs tm = step (onset . head $ vs) . foldr step tm $ (toIOIs vs)
step :: Time -> TickMap -> TickMap
step (Time se) tm = insertWith succIfExists se 0 tm
succIfExists :: Time -> Time -> Time
succIfExists _ old = succ old
nrOfNotes :: MidiScore -> Int
nrOfNotes = sum . map length . getVoices
isTimeSig :: Timed ScoreEvent -> Bool
isTimeSig (Timed _ (TimeSigChange _ )) = True
isTimeSig _ = False
isKeyChange :: Timed ScoreEvent -> Bool
isKeyChange (Timed _ (KeyChange _ )) = True
isKeyChange _ = False
isTempoChange :: Timed ScoreEvent -> Bool
isTempoChange (Timed _ (TempoChange _ )) = True
isTempoChange _ = False
isNoteEvent :: Timed ScoreEvent -> Bool
isNoteEvent (Timed _ (NoteEvent _ _ _ _ )) = True
isNoteEvent _ = False
pitchClass :: Pitch -> PitchClass
pitchClass (Pitch (_, pc)) = pc
getPitch :: Timed ScoreEvent -> Pitch
getPitch tse = case getEvent tse of
(NoteEvent _c p _v _d) -> p
se -> error ("unexpected ScoreEvent: " ++ show se)
getInterval :: Pitch -> Pitch -> Interval
getInterval (Pitch (Octave fo, PitchClass fpc))
(Pitch (Octave to, PitchClass tpc)) =
let (oct', pc') = divMod (tpc fpc) 12
in Interval ((12 * (to fo + oct')) + pc')
changePitch :: Pitch -> Interval -> Pitch
changePitch (Pitch (Octave oct, PitchClass pc)) (Interval i) =
let (octi, pci) = divMod i 12
(oct', pc') = divMod (pc + pci) 12
in Pitch (Octave (oct + octi + oct'), PitchClass pc')
toOnsets :: Voice -> [Time]
toOnsets = Sort.nub . map onset
toIOIs :: Voice -> [Time]
toIOIs v = execState (foldrM step [] v) [] where
step :: Timed ScoreEvent -> [Timed ScoreEvent]
-> State [Time] [Timed ScoreEvent]
step t [] = return [t]
step t ts@(h : _) = do modify ((onset h onset t) :)
return (t : ts)
toMidiNr :: Pitch -> Word8
toMidiNr (Pitch (Octave o, PitchClass p)) = fromIntegral (((o + 5) * 12) + p)
toPitch :: Word8 -> Pitch
toPitch = Pitch . (Octave *** PitchClass) . midiNrToPitch where
midiNrToPitch :: Word8 -> (Int, Int)
midiNrToPitch p | p < 0 = invalidMidiNumberError p
| p > 127 = invalidMidiNumberError p
| otherwise = first (+ (5)) (fromIntegral p `divMod` 12)
hasTimeSigs :: MidiScore -> Bool
hasTimeSigs = not . null . filter (not . (== NoTimeSig) . getEvent) . getTimeSig
updateTimeSig :: MidiScore -> Timed TimeSig -> Timed TimeSig
-> Either String MidiScore
updateTimeSig ms old new
| ts == ts' = Left ("updateTimeSig: TimeSig " ++ show old ++ " not found")
| otherwise = Right $ ms {getTimeSig = sort (new : ts') }
where ts = getTimeSig ms
ts' = filter (== old) ts
hasNotes :: MidiTrack -> Bool
hasNotes = isJust . find isNoteOnEvent . getTrackMessages
isNoteOnEvent :: MidiMessage -> Bool
isNoteOnEvent (_, (VoiceEvent _ (NoteOn _ _ _))) = True
isNoteOnEvent _ = False
removeLabels :: MidiFile -> MidiFile
removeLabels f = f { mf_tracks = map filterLab . mf_tracks $ f } where
filterLab :: MidiTrack -> MidiTrack
filterLab = MidiTrack . filter (not . isLab) . getTrackMessages
isLab :: MidiMessage -> Bool
isLab (_, (MetaEvent (TextEvent _ _))) = True
isLab _ = False