module ZMidi.Score.Show ( showMidiScore
, showVoices
) where
import ZMidi.Score.Datatypes
import Control.Monad.State ( State, modify, get
, evalState )
import Control.Monad ( mapAndUnzipM )
import Data.List ( intercalate )
import Text.Printf ( printf )
showMidiScore :: MidiScore -> String
showMidiScore ms@(MidiScore k ts tb mf tp st _vs) = "Key: " ++ show k
++ "\nMeter: " ++ show ts
++ "\nTicks per Beat: " ++ show tb
++ "\nMidi format: " ++ show mf
++ "\nTempo: " ++ show tp
++ "\nShortest tick: " ++ show st
++ "\nNotes:\n" ++ showVoices ms
showVoices :: MidiScore -> String
showVoices ms = intercalate "\n" $ evalState (showTimeSlice . getVoices $ ms) 0
where
showTimeSlice :: [Voice] -> State Time [String]
showTimeSlice vs =
do (str, vs') <- mapAndUnzipM showVoiceAtTime vs
case noMoreNotesToShow vs' of
True -> return []
False -> do t <- get
modify (+ minDur ms)
x <- showTimeSlice vs'
let out = intercalate "\t" (printf "%7d" (time t) : str)
return (out : x)
noMoreNotesToShow :: [Voice] -> Bool
noMoreNotesToShow = and . map null
showVoiceAtTime :: Voice -> State Time (String, Voice)
showVoiceAtTime [] = return (" ",[])
showVoiceAtTime x@(v:vs) =
do t <- get
case hasStarted t v of
True -> case hasEnded t v of
True -> showVoiceAtTime vs
False -> return (show . pitch . getEvent $ v, x)
False -> return (" " , x)
hasStarted, hasEnded :: Time -> Timed ScoreEvent -> Bool
hasStarted t tse = t >= onset tse
hasEnded t (Timed ons se) = ons + duration se < t