event-list-0.1.1.2: Event lists with relative or absolute time stamps

Copyright(c) Henning Thielemann 2007-2010
Maintainerhaskell@henning-thielemann.de
Stabilitystable
PortabilityHaskell 98
Safe HaskellSafe-Inferred
LanguageHaskell98

Data.EventList.Relative.TimeTime

Description

Event lists starting with a time difference and ending with a time difference.

Synopsis

Documentation

data T time body Source

Instances

Functor (T time) 
Foldable (T time) 
Traversable (T time) 
(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) 
C time => Monoid (T time body) 

mapBody :: (body0 -> body1) -> T time body0 -> T time body1 Source

mapTime :: (time0 -> time1) -> T time0 body -> T time1 body Source

zipWithBody :: (body0 -> body1 -> body2) -> [body0] -> T time body1 -> T time body2 Source

zipWithTime :: (time0 -> time1 -> time2) -> (time0, [time0]) -> T time1 body -> T time2 body Source

unzip :: T time (body0, body1) -> (T time body0, T time body1) Source

concatMapMonoid :: Monoid m => (time -> m) -> (body -> m) -> T time body -> m Source

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 :: C time => T time body -> time Source

merge :: (C time, Ord body) => T time body -> T time body -> T time body Source

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 body Source

insert :: (C time, Ord body) => time -> body -> T time body -> T time body Source

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 Haskore/section equivalence. It is also necessary to assert a unique representation of the event list independent of the structure of the event type. The same function for inserting into a time ordered list with a trailing pause.

pad :: C time => time -> T time body -> T time body Source

moveForward :: (Ord time, Num time) => T time (time, body) -> T time body Source

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 body Source

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 body Source

arrange :: (Ord body, C time) => T time (T time body) -> T time body Source

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 body Source

moveForwardRestrictedBy :: C time => (body -> body -> Bool) -> time -> T time (time, body) -> T time body Source

currently only for testing

moveForwardRestrictedByQueue :: (C time, Num time) => (body -> body -> Bool) -> time -> T time (time, body) -> T time body Source

currently only for testing

moveForwardRestrictedByStrict :: C time => (body -> body -> Bool) -> time -> T time (time, body) -> T time body Source

currently only for testing

decreaseStart :: C time => time -> T time body -> T time body Source

delay :: C time => time -> T time body -> T time body Source

filter :: C time => (body -> Bool) -> T time body -> T time body Source

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 :: C time => (body -> Bool) -> T time body -> (T time body, T time body) Source

partitionMaybe :: C time => (body0 -> Maybe body1) -> T time body0 -> (T time body1, T time body0) Source

partitionMaybeR :: C time => (body0 -> Maybe body1) -> T time body0 -> (T time body1, T time body0) Source

slice :: (Eq a, C 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 -> b Source

foldl :: (a -> time -> b) -> (b -> body -> a) -> a -> T time body -> b Source

pause :: time -> T time body Source

isPause :: T time body -> Bool Source

cons :: time -> body -> T time body -> T time body Source

snoc :: T time body -> body -> time -> T time body Source

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 -> a Source

switchR :: (time -> a) -> (T time body -> body -> time -> a) -> T time body -> a Source

mapMaybe :: C time => (body0 -> Maybe body1) -> T time body0 -> T time body1 Source

catMaybes :: C time => T time (Maybe body) -> T time body Source

Adds times in a left-associative fashion. Use this if the time is a strict data type.

catMaybesR :: C time => T time (Maybe body) -> T time body Source

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 body Source

concat :: C time => [T time body] -> T time body Source

concatNaive :: C time => [T time body] -> T time body Source

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 body Source

Uses sharing.

cycleNaive :: C time => T time body -> T time body Source

reverse :: T time body -> T time body Source

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 body Source

dropTime :: C time => time -> T time body -> T time body Source

forceTimeHead :: C time => T time body -> T time body Source

discretize :: (C time, RealFrac time, C i, Integral i) => T time body -> T i body Source

resample :: (C time, RealFrac time, C i, Integral i) => time -> T time body -> T i body Source

collectCoincident :: C time => T time body -> T time [body] Source

flatten :: C time => T time [body] -> T time body Source

mapCoincident :: C time => ([a] -> [b]) -> T time a -> T time b Source

normalize :: (Ord body, C time) => T time body -> T time body Source

Sort coincident elements.

isNormalized :: (C time, Ord body) => T time body -> Bool Source

toAbsoluteEventList :: Num time => time -> T time body -> T time body Source

fromAbsoluteEventList :: Num time => T time body -> T time body Source