module Music.Theory.Time.Notation where
import Text.Printf
type FSEC = Double
type MINSEC = (Int,Int)
type MINCSEC = (Int,Int,Int)
fsec_to_minsec :: FSEC -> MINSEC
fsec_to_minsec tm = round tm `divMod` 60
minsec_pp :: MINSEC -> String
minsec_pp (m,s) = printf "%02d:%02d" m s
fsec_to_mincsec :: FSEC -> MINCSEC
fsec_to_mincsec tm =
let tm' = floor tm
(m,s) = tm' `divMod` 60
cs = round ((tm fromIntegral tm') * 100)
in (m,s,cs)
mincsec_pp :: MINCSEC -> String
mincsec_pp (m,s,cs) = printf "%02d:%02d.%02d" m s cs
span_pp :: (t -> String) -> (t,t) -> String
span_pp f (t1,t2) = concat [f t1," - ",f t2]