haskore-realtime-0.1: Routines for realtime playback of Haskore songsSource codeContentsIndex
Haskore.RealTime.EventList.TimeBody
Description
Apply actions to event lists (starting with time, ending with body) at given times.
Synopsis
data T time body
mapBodyM :: Monad m => (body0 -> m body1) -> T time body0 -> m (T time body1)
mapM :: Monad m => (time0 -> m time1) -> (body0 -> m body1) -> T time0 body0 -> m (T time1 body1)
mapM_ :: Monad m => (time -> m ()) -> (body -> m ()) -> T time body -> m ()
getBodies :: T time body -> [body]
mapBody :: (body0 -> body1) -> T time body0 -> T time body1
mapTime :: (time0 -> time1) -> T time0 body -> T time1 body
mapTimeTail :: (T time body0 -> T time body1) -> T time body0 -> T time body1
empty :: T time body
singleton :: time -> body -> T time body
null :: T time body -> Bool
viewL :: T time body -> Maybe ((time, body), T time body)
viewTimeL :: T time body -> Maybe (time, T time body)
viewBodyL :: T time body -> (body, T time body)
cons :: time -> body -> T time body -> T time body
snoc :: T time body -> time -> body -> T time body
consBody :: body -> T time body -> T time body
consTime :: time -> T time body -> T time body
append :: T time body -> T time body -> T time body
concat :: [T time body] -> T time body
cycle :: T time body -> T time body
insert :: (C time, Ord body) => time -> body -> T time body -> T time body
decreaseStart :: C time => time -> T time body -> T time body
delay :: C time => time -> T time body -> T time body
partition :: Num time => (body -> Bool) -> T time body -> (T time body, T time body)
foldr :: (time -> a -> b) -> (body -> b -> a) -> b -> T time body -> b
slice :: (Eq a, Num time) => (body -> a) -> T time body -> [(a, T time body)]
normalize :: (C time, Ord body) => T time body -> T time body
collectCoincident :: C time => T time body -> T time [body]
flatten :: C time => T time [body] -> T time body
mapCoincident :: C time => ([a] -> [b]) -> T time a -> T time b
resample :: (C time, RealFrac time, C i, Integral i) => time -> T time body -> T i body
toAbsoluteEventList :: Num time => time -> T time body -> T time body
run :: (RealFrac time, Monad m) => T m -> (body -> m a) -> T time body -> m [a]
runTimeStamp :: (RealFrac time, Monad m) => T m -> (time -> body -> m a) -> T time body -> m [a]
runTimeStampGrouped :: (RealFrac time, Monad m) => T m -> (time -> [body] -> m a) -> T time body -> m [a]
runCore :: (Fractional time0, RealFrac time1, Monad m) => (T time0 body0 -> T time1 body1) -> T m -> (time1 -> body1 -> m a) -> T time0 body0 -> m [a]
runRelative :: (C time, RealFrac time, Monad m) => T m -> (body -> m a) -> T time body -> m [a]
runRelativeCore :: Monad m => T m -> (body -> m a) -> T Integer body -> m [a]
attachTime :: T time body -> T time (time, body)
Documentation
data T time body Source
show/hide Instances
(Eq time, Eq body) => Eq (T time body)
(Ord time, Ord body) => Ord (T time body)
(Show time, Show body) => Show (T time body)
(Arbitrary time, Arbitrary body) => Arbitrary (T time body)
mapBodyM :: Monad m => (body0 -> m body1) -> T time body0 -> m (T time body1)Source
mapM :: Monad m => (time0 -> m time1) -> (body0 -> m body1) -> T time0 body0 -> m (T time1 body1)Source
mapM_ :: Monad m => (time -> m ()) -> (body -> m ()) -> T time body -> m ()Source
getBodies :: T time body -> [body]Source
mapBody :: (body0 -> body1) -> T time body0 -> T time body1Source
mapTime :: (time0 -> time1) -> T time0 body -> T time1 bodySource
mapTimeTail :: (T time body0 -> T time body1) -> T time body0 -> T time body1Source
empty :: T time bodySource
singleton :: time -> body -> T time bodySource
null :: T time body -> BoolSource
viewL :: T time body -> Maybe ((time, body), T time body)Source
viewTimeL :: T time body -> Maybe (time, T time body)Source
viewBodyL :: T time body -> (body, T time body)Source
cons :: time -> body -> T time body -> T time bodySource
snoc :: T time body -> time -> body -> T time bodySource
consBody :: body -> T time body -> T time bodySource
consTime :: time -> T time body -> T time bodySource
append :: T time body -> T time body -> T time bodySource
concat :: [T time body] -> T time bodySource
cycle :: T time body -> T time bodySource
insert :: (C time, Ord body) => time -> body -> T time body -> T time bodySource
insert inserts an event into an event list at the given time.
decreaseStart :: C time => time -> T time body -> T time bodySource
delay :: C time => time -> T time body -> T time bodySource
partition :: Num time => (body -> Bool) -> T time body -> (T time body, T time body)Source
foldr :: (time -> a -> b) -> (body -> b -> a) -> b -> T time body -> bSource
slice :: (Eq a, Num time) => (body -> a) -> T time body -> [(a, T time body)]Source
Using a classification function we splice the event list into lists, each containing the same class. Absolute time stamps are preserved.
normalize :: (C time, Ord body) => T time body -> T time bodySource
sort sorts a list of coinciding events, that is all events but the first one have time difference 0. normalize sorts all coinciding events in a list thus yielding a canonical representation of a time ordered list.
collectCoincident :: C time => T time body -> T time [body]Source
Group events that have equal start times (that is zero time differences).
flatten :: C time => T time [body] -> T time bodySource

Reverse to collectCoincident: Turn each body into a separate event.

   xs  ==  flatten (collectCoincident xs)
mapCoincident :: C time => ([a] -> [b]) -> T time a -> T time bSource
Apply a function to the lists of coincident events.
resample :: (C time, RealFrac time, C i, Integral i) => time -> T time body -> T i bodySource
toAbsoluteEventList :: Num time => time -> T time body -> T time bodySource
We tried hard to compute everything with respect to relative times. However sometimes we need absolute time values.
run :: (RealFrac time, Monad m) => T m -> (body -> m a) -> T time body -> m [a]Source

The next set of routines is more precise. It computes a time table starting with current system time and tries to stick to it.

So far, I worked hard to use time differences instead of absolute times in order to avoid increasing memory consumption of time numbers (which however slows down as time evolves) but the time related functions of the system are absolute, so have to make our ones absolute as well.

runTimeStamp :: (RealFrac time, Monad m) => T m -> (time -> body -> m a) -> T time body -> m [a]Source
The wait calls are necessarily quantized, but the time passed to the action is not quantized.
runTimeStampGrouped :: (RealFrac time, Monad m) => T m -> (time -> [body] -> m a) -> T time body -> m [a]Source
This routine is only necessary, because differences might be too small to be noticed in the absolute time values. That is, collectCoincident will split events which actually belong together.
runCore :: (Fractional time0, RealFrac time1, Monad m) => (T time0 body0 -> T time1 body1) -> T m -> (time1 -> body1 -> m a) -> T time0 body0 -> m [a]Source
runRelative :: (C time, RealFrac time, Monad m) => T m -> (body -> m a) -> T time body -> m [a]Source
The first function assumes, that the action does not consume time and that the wait command is precise. It is not very useful in practice, but very simple.
runRelativeCore :: Monad m => T m -> (body -> m a) -> T Integer body -> m [a]Source
attachTime :: T time body -> T time (time, body)Source
We export this function only for use in Haskore.RealTime.EventList.TimeTime.
Produced by Haddock version 2.7.2