
ties are a presentation-level issue, the underlying (sound) representation is a single note. i suggest Doc = [Note] where Notes have fields for their measure location and duration. then there's no issue with overlapping notes, and start/end times are easy to calculate. ties can be calculated easily later for graphical layout by asking if durations overlap given boundaries (usually measure boundaries, but also measure centers). i use a natural rhythm EDSL here: http://code.google.com/p/h1ccup/source/browse/trunk/theory/haskell/src/LiveC... here's the rhythm-related part (doesn't handle varying tempo). it lets you say things like: Note {measure = 3, beat = 2, dur = Dotted $ Triplet Quarter} ------------------------ {-# LANGUAGE ExistentialQuantification, ScopedTypeVariables, RecordWildCards, RankNTypes #-} tempo = 200 -- bpm timeSig = TimeSig { numBeats = 4 , unit = Quarter } data DurBase = Whole | Half | Quarter | Eighth | Sixteenth | ThirtySecond deriving (Enum, Bounded, Show, Eq) data ModDur = forall x. NoteDur x => Dotted x | Triplet DurBase data TimeSig = TimeSig { numBeats :: Int , unit :: DurBase } data Note = forall x . NoteDur x => Note { midiNum :: Int -- 0-255 , vel :: Int -- 0-255 , chan :: Int -- 0-15 , measure :: Integral a => a , beat :: Int , subdiv :: (Real a, Fractional a) => a -- % of beat , dur :: x } class NoteDur a where quarters :: (Real x, Fractional x) => a -> x calcDurMS :: (Real x, Fractional x) => a -> x calcDurMS d = 1000 * 60 * beats d / realToFrac tempo beats :: (Real x, Fractional x) => a -> x beats d = uncurry (/) $ both quarters (d, unit timeSig) where both (f :: forall a b. (NoteDur a, Real b, Fractional b) => a -> b) (x, y) = (f x, f y) instance NoteDur DurBase where quarters x = z where Just z = lookup x . zip [minBound .. maxBound] $ map (fromRational . (2 ^^)) [2, 1 ..] instance NoteDur ModDur where quarters (Dotted x) = quarters x * 3 / 2 quarters (Triplet x) = quarters x * 2 / 3 instance NoteDur Note where quarters Note{..} = quarters dur calcStartMS :: (Real a, Fractional a) => Note -> a calcStartMS n = realToFrac (subdiv n + (fromIntegral $ (measure n * numBeats timeSig) + beat n)) * (calcDurMS $ unit timeSig) measureMS :: (Real a, Fractional a) => a measureMS = calcStartMS Note { measure = 1 , beat = 0 , subdiv = 0 , midiNum = undefined , vel = undefined , chan = undefined , dur = undefined :: DurBase -- ugh } -e