event-list-0.0.10: Event lists with relative or absolute time stampsSource codeContentsIndex
Data.EventList.Relative.TimeTime
PortabilityHaskell 98
Stabilitystable
Maintainerhaskell@henning-thielemann.de
Description
Event lists starting with a time difference and ending with a time difference.
Synopsis
data T time body
mapBody :: (body0 -> body1) -> T time body0 -> T time body1
mapTime :: (time0 -> time1) -> T time0 body -> T time1 body
zipWithBody :: (body0 -> body1 -> body2) -> [body0] -> T time body1 -> T time body2
zipWithTime :: (time0 -> time1 -> time2) -> (time0, [time0]) -> T time1 body -> T time2 body
concatMapMonoid :: Monoid m => (time -> m) -> (body -> m) -> T time body -> m
traverse :: Applicative m => (time0 -> m time1) -> (body0 -> m body1) -> T time0 body0 -> m (T time1 body1)
traverse_ :: Applicative m => (time -> m ()) -> (body -> m ()) -> T time body -> m ()
traverseBody :: Applicative m => (body0 -> m body1) -> T time body0 -> m (T time body1)
traverseTime :: Applicative m => (time0 -> m time1) -> T time0 body -> m (T time1 body)
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 ()
mapBodyM :: Monad m => (body0 -> m body1) -> T time body0 -> m (T time body1)
mapTimeM :: Monad m => (time0 -> m time1) -> T time0 body -> m (T time1 body)
getTimes :: T time body -> [time]
getBodies :: T time body -> [body]
duration :: Num time => T time body -> time
merge :: (C time, Ord body) => T time body -> T time body -> T time body
mergeBy :: C time => (body -> body -> Bool) -> T time body -> T time body -> T time body
insert :: (C time, Ord body) => time -> body -> T time body -> T time body
pad :: C time => time -> T time body -> T time body
moveForward :: C time => T time (time, body) -> T time body
moveForwardRestricted :: (Ord body, C time) => time -> T time (time, body) -> T time body
moveBackward :: C time => T time (time, body) -> T time body
arrange :: (Ord body, C time) => T time (T time body) -> T time body
arrangeBy :: C time => (body -> body -> Bool) -> T time (T time body) -> T time body
moveForwardRestrictedBy :: C time => (body -> body -> Bool) -> time -> T time (time, body) -> T time body
moveForwardRestrictedByQueue :: C time => (body -> body -> Bool) -> time -> T time (time, body) -> T time body
moveForwardRestrictedByStrict :: C time => (body -> body -> Bool) -> time -> T time (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
filter :: Num time => (body -> Bool) -> T time body -> T time body
partition :: Num time => (body -> Bool) -> T time body -> (T time body, T time body)
slice :: (Eq a, Num time) => (body -> a) -> T time body -> [(a, T time body)]
foldr :: (time -> a -> b) -> (body -> b -> a) -> a -> T time body -> b
pause :: time -> T time body
isPause :: T time body -> Bool
cons :: time -> body -> T time body -> T time body
snoc :: T time body -> body -> time -> T time body
viewL :: T time body -> (time, Maybe (body, T time body))
viewR :: T time body -> (Maybe (T time body, body), time)
switchL :: (time -> a) -> ((time, body) -> T time body -> a) -> T time body -> a
switchR :: (time -> a) -> (T time body -> body -> time -> a) -> T time body -> a
mapMaybe :: Num time => (body0 -> Maybe body1) -> T time body0 -> T time body1
catMaybes :: Num time => T time (Maybe body) -> T time body
catMaybesR :: Num time => T time (Maybe body) -> T time body
append :: C time => T time body -> T time body -> T time body
concat :: C time => [T time body] -> T time body
concatNaive :: C time => [T time body] -> T time body
cycle :: C time => T time body -> T time body
cycleNaive :: C time => T time body -> T time body
splitAtTime :: C time => time -> T time body -> (T time body, T time body)
takeTime :: C time => time -> T time body -> T time body
dropTime :: C time => time -> T time body -> T time body
discretize :: (C time, RealFrac time, C i, Integral i) => T time body -> T i body
resample :: (C time, RealFrac time, C i, Integral i) => time -> T time body -> T i body
collectCoincident :: C time => T time body -> T time [body]
flatten :: Num time => T time [body] -> T time body
mapCoincident :: C time => ([a] -> [b]) -> T time a -> T time b
normalize :: (Ord body, C time) => T time body -> T time body
isNormalized :: (C time, Ord body) => T time body -> Bool
toAbsoluteEventList :: Num time => time -> T time body -> T time body
fromAbsoluteEventList :: Num time => T time body -> T 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)
mapBody :: (body0 -> body1) -> T time body0 -> T time body1Source
mapTime :: (time0 -> time1) -> T time0 body -> T time1 bodySource
zipWithBody :: (body0 -> body1 -> body2) -> [body0] -> T time body1 -> T time body2Source
zipWithTime :: (time0 -> time1 -> time2) -> (time0, [time0]) -> T time1 body -> T time2 bodySource
concatMapMonoid :: Monoid m => (time -> m) -> (body -> m) -> T time body -> mSource
traverse :: Applicative m => (time0 -> m time1) -> (body0 -> m body1) -> T time0 body0 -> m (T time1 body1)Source
traverse_ :: Applicative m => (time -> m ()) -> (body -> m ()) -> T time body -> m ()Source
traverseBody :: Applicative m => (body0 -> m body1) -> T time body0 -> m (T time body1)Source
traverseTime :: Applicative m => (time0 -> m time1) -> T time0 body -> m (T time1 body)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
mapBodyM :: Monad m => (body0 -> m body1) -> T time body0 -> m (T time body1)Source
mapTimeM :: Monad m => (time0 -> m time1) -> T time0 body -> m (T time1 body)Source
getTimes :: T time body -> [time]Source
getBodies :: T time body -> [body]Source
duration :: Num time => T time body -> timeSource
merge :: (C time, Ord body) => T time body -> T time body -> T time bodySource
The first important function is merge which merges the events of two lists into a new time order list.
mergeBy :: C time => (body -> body -> Bool) -> T time body -> T time body -> T time bodySource
insert :: (C time, Ord body) => time -> body -> T time body -> T time bodySource

Note that merge compares entire events rather than just start times. This is to ensure that it is commutative, a desirable condition for some of the proofs used in secref{equivalence}. It is also necessary to assert a unique representation of the performance independent of the structure of the 'Music.T note'. The same function for inserting into a time ordered list with a trailing pause. The strictness annotation is necessary for working with infinite lists.

Here are two other functions that are already known for non-padded time lists.

pad :: C time => time -> T time body -> T time bodySource
moveForward :: C time => T time (time, body) -> T time bodySource
Move events towards the front of the event list. You must make sure, that no event is moved before time zero. This works only for finite lists.
moveForwardRestricted :: (Ord body, C time) => time -> T time (time, body) -> T time bodySource
Like moveForward but restricts the look-ahead time. For moveForwardRestricted maxTimeDiff xs all time differences (aka the moveForward offsets) in xs must be at most maxTimeDiff. With this restriction the function is lazy enough for handling infinite event lists. However the larger maxTimeDiff the more memory and time is consumed.
moveBackward :: C time => T time (time, body) -> T time bodySource
arrange :: (Ord body, C time) => T time (T time body) -> T time bodySource
Merge several event lists respecting the start time of the outer event list.
arrangeBy :: C time => (body -> body -> Bool) -> T time (T time body) -> T time bodySource
moveForwardRestrictedBy :: C time => (body -> body -> Bool) -> time -> T time (time, body) -> T time bodySource
currently only for testing
moveForwardRestrictedByQueue :: C time => (body -> body -> Bool) -> time -> T time (time, body) -> T time bodySource
currently only for testing
moveForwardRestrictedByStrict :: C time => (body -> body -> Bool) -> time -> T time (time, body) -> T time bodySource
currently only for testing
decreaseStart :: C time => time -> T time body -> T time bodySource
delay :: C time => time -> T time body -> T time bodySource
filter :: Num time => (body -> Bool) -> T time body -> T time bodySource
Analogously to the concat / concatNaive pair we have to versions of filter, where the clever implementation sums up pauses from the beginning to the end.
partition :: Num time => (body -> Bool) -> T time body -> (T time body, T time body)Source
slice :: (Eq a, Num time) => (body -> a) -> T time body -> [(a, T time body)]Source
Since we need it later for MIDI generation, we will also define a slicing into equivalence classes of events.
foldr :: (time -> a -> b) -> (body -> b -> a) -> a -> T time body -> bSource
pause :: time -> T time bodySource
isPause :: T time body -> BoolSource
cons :: time -> body -> T time body -> T time bodySource
snoc :: T time body -> body -> time -> T time bodySource
viewL :: T time body -> (time, Maybe (body, T time body))Source
viewR :: T time body -> (Maybe (T time body, body), time)Source
switchL :: (time -> a) -> ((time, body) -> T time body -> a) -> T time body -> aSource
switchR :: (time -> a) -> (T time body -> body -> time -> a) -> T time body -> aSource
mapMaybe :: Num time => (body0 -> Maybe body1) -> T time body0 -> T time body1Source
catMaybes :: Num time => T time (Maybe body) -> T time bodySource
Adds times in a left-associative fashion. Use this if the time is a strict data type.
catMaybesR :: Num time => T time (Maybe body) -> T time bodySource
Adds times in a right-associative fashion. Use this if the time is a data type like lazy Peano numbers or Numeric.NonNegative.Chunky.
append :: C time => T time body -> T time body -> T time bodySource
concat :: C time => [T time body] -> T time bodySource
concatNaive :: C time => [T time body] -> T time bodySource
concat and concatNaive are essentially the same. concat must use foldr in order to work on infinite lists, however if there are many empty lists, summing of their durations will be done from right to left, which is inefficient. Thus we detect subsequent empty lists and merge them from left to right.
cycle :: C time => T time body -> T time bodySource
Uses sharing.
cycleNaive :: C time => T time body -> T time bodySource
splitAtTime :: C time => time -> T time body -> (T time body, T time body)Source
If there is an event at the cutting time, this event is returned in the suffix part. That is splitAtTime t0 (t0 . x . t1 ./ empty) == (pause t0, 0 . x . t1 ./ empty)
takeTime :: C time => time -> T time body -> T time bodySource
dropTime :: C time => time -> T time body -> T time bodySource
discretize :: (C time, RealFrac time, C i, Integral i) => T time body -> T i bodySource
resample :: (C time, RealFrac time, C i, Integral i) => time -> T time body -> T i bodySource
collectCoincident :: C time => T time body -> T time [body]Source
flatten :: Num time => T time [body] -> T time bodySource
mapCoincident :: C time => ([a] -> [b]) -> T time a -> T time bSource
normalize :: (Ord body, C time) => T time body -> T time bodySource
Sort coincident elements.
isNormalized :: (C time, Ord body) => T time body -> BoolSource
toAbsoluteEventList :: Num time => time -> T time body -> T time bodySource
fromAbsoluteEventList :: Num time => T time body -> T time bodySource
Produced by Haddock version 2.4.2