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

PortabilityHaskell 98
Stabilitystable
Maintainerhaskell@henning-thielemann.de

Data.EventList.Relative.TimeBody

Description

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

The time is stored in differences between the events. Thus there is no increase of time information for long, or even infinite, streams of events. Further on, the time difference is stored in the latter of two neighbouring events. This is necessary for real-time computing where it is not known whether and when the next event happens.

Synopsis

Documentation

data T time body Source

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) 

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

viewR :: T time body -> Maybe (T time body, (time, body))Source

cons :: time -> body -> T time body -> T time bodySource

snoc :: T time body -> time -> body -> T time bodySource

fromPairList :: [(a, b)] -> T a bSource

toPairList :: T a b -> [(a, b)]Source

getTimes :: T time body -> [time]Source

getBodies :: T time body -> [body]Source

duration :: Num time => T time body -> timeSource

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

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

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

foldr :: (time -> a -> b) -> (body -> b -> a) -> b -> T time body -> bSource

foldrPair :: (time -> body -> a -> a) -> a -> T time body -> aSource

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

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.

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

The final critical function is insert, which inserts an event into an already time-ordered sequence of events. For instance it is used in MidiFiles to insert a NoteOff event into a list of NoteOn and NoteOff events.

insertBy :: (C time, Ord body) => (body -> body -> Bool) -> time -> body -> T time body -> T time bodySource

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

The function partition is somehow the inverse to merge. It is similar to partition. We could use the List function if the event times would be absolute, because then the events need not to be altered on splits. But absolute time points can't be used for infinite music thus we take the burden of adapting the time differences when an event is removed from the performance list and put to the list of events of a particular instrument. t0 is the time gone since the last event in the first partition, t1 is the time gone since the last event in the second partition.

Note, that using Data.EventList.Utility.mapPair we circumvent the following problem: Since the recursive call to partition may end up with Bottom, pattern matching with, say expression{(es0,es1)}, will halt the bounding of the variables until the most inner call to partition is finished. This never happens. If the pair constructor is made strict, that is we write expression{~(es0,es1)}, then everything works. Also avoiding pattern matching and using fst and snd would help.

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.

span :: (body -> Bool) -> T time body -> (T time body, T time body)Source

mapMaybe :: Num time => (body0 -> Maybe body1) -> T time body0 -> T time body1Source

catMaybes :: Num time => T time (Maybe body) -> T time bodySource

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.

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

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

We will also sometimes need a function which groups events by equal start times. This implementation is not so obvious since we work with time differences. The criterion is: Two neighbouring events start at the same time if the second one has zero time difference.

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

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

Apply a function to the lists of coincident events.

append :: T time body -> T time body -> T time bodySource

concat :: [T time body] -> T time bodySource

cycle :: T time body -> T time bodySource

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

We provide discretize and resample for discretizing the time information. When converting the precise relative event times to the integer relative event times we have to prevent accumulation of rounding errors. We avoid this problem with a stateful conversion which remembers each rounding error we make. This rounding error is used to correct the next rounding. Given the relative time and duration of an event the function floorDiff creates a Control.Monad.State.State which computes the rounded relative time. It is corrected by previous rounding errors.

The resulting event list may have differing time differences which were equal before discretization, but the overall timing is uniformly close to the original.

We use floorDiff rather than roundDiff in order to compute exclusively with non-negative numbers.

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.

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