Copyright | (c) Henning Thielemann 2007-2010 |
---|---|
Maintainer | haskell@henning-thielemann.de |
Stability | stable |
Portability | Haskell 98 |
Safe Haskell | Safe |
Language | Haskell98 |
- data T time body
- 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)
- viewR :: T time body -> Maybe (T time body, (time, body))
- switchL :: c -> ((time, body) -> T time body -> c) -> T time body -> c
- switchR :: c -> (T time body -> (time, body) -> c) -> T time body -> c
- cons :: time -> body -> T time body -> T time body
- snoc :: T time body -> time -> body -> T time body
- fromPairList :: [(a, b)] -> T a b
- toPairList :: T a b -> [(a, b)]
- getTimes :: T time body -> [time]
- getBodies :: T time body -> [body]
- duration :: Num time => T time body -> time
- mapBody :: (body0 -> body1) -> T time body0 -> T time body1
- mapTime :: (time0 -> time1) -> T time0 body -> T time1 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)
- merge :: (Ord time, Ord body) => T time body -> T time body -> T time body
- mergeBy :: Ord time => (body -> body -> Bool) -> T time body -> T time body -> T time body
- insert :: (Ord time, Ord body) => time -> body -> T time body -> T time body
- insertBy :: Ord time => (body -> body -> Bool) -> time -> body -> T time body -> T time body
- moveForward :: (Ord time, Num time) => T time (time, body) -> T time body
- decreaseStart :: (Ord time, Num time) => time -> T time body -> T time body
- delay :: (Ord time, Num time) => time -> T time body -> T time body
- filter :: Num time => (body -> Bool) -> T time body -> T time body
- partition :: (body -> Bool) -> T time body -> (T time body, T time body)
- partitionMaybe :: (body0 -> Maybe body1) -> T time body0 -> (T time body1, T time body0)
- slice :: Eq a => (body -> a) -> T time body -> [(a, T time body)]
- foldr :: (time -> a -> b) -> (body -> b -> a) -> b -> T time body -> b
- foldrPair :: (time -> body -> a -> a) -> 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
- normalize :: (Ord time, Num time, Ord body) => T time body -> T time body
- isNormalized :: (Ord time, Num time, Ord body) => T time body -> Bool
- collectCoincident :: Eq time => T time body -> T time [body]
- flatten :: Ord time => T time [body] -> T time body
- mapCoincident :: Ord time => ([a] -> [b]) -> T time a -> T time b
- append :: (Ord time, Num time) => T time body -> T time body -> T time body
- concat :: (Ord time, Num time) => [T time body] -> T time body
- cycle :: (Ord time, Num time) => T time body -> T time body
- discretize :: (RealFrac time, Integral i) => T time body -> T i body
- resample :: (RealFrac time, Integral i) => time -> T time body -> T i body
- checkTimes :: Ord time => T time body -> T time body
- collectCoincidentFoldr :: Eq time => T time body -> T time [body]
- collectCoincidentNonLazy :: Eq time => T time body -> T time [body]
Documentation
Functor (T time) Source # | |
Foldable (T time) Source # | |
Traversable (T time) Source # | |
(Eq body, Eq time) => Eq (T time body) Source # | |
(Ord body, Ord time) => Ord (T time body) Source # | |
(Show body, Show time) => Show (T time body) Source # | |
(Num time, Ord time) => Semigroup (T time body) Source # | |
(Num time, Ord time) => Monoid (T time body) Source # | |
(Arbitrary time, Arbitrary body) => Arbitrary (T time body) Source # | |
fromPairList :: [(a, b)] -> T a b Source #
toPairList :: T a b -> [(a, b)] Source #
duration :: Num time => T time body -> time Source #
Duration of an empty event list is considered zero. However, I'm not sure if this is sound.
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 #
merge :: (Ord 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 :: Ord time => (body -> body -> Bool) -> T 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 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 :: (Ord time, Ord body) => time -> body -> T time body -> T time body Source #
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 :: Ord time => (body -> body -> Bool) -> time -> body -> 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.
slice :: Eq a => (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.
collectCoincident :: Eq 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.
mapCoincident :: Ord time => ([a] -> [b]) -> T time a -> T time b Source #
Apply a function to the lists of coincident events.
discretize :: (RealFrac time, Integral i) => T time body -> T i body Source #
Here are some functions 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 a note
the function discretizeEventM
creates a 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.
checkTimes :: Ord time => T time body -> T time body Source #
Check whether time values are in ascending order.
The list is processed lazily and
times that are smaller than there predecessors are replaced by undefined
.
If you would remove the undefined
times from the resulting list
the times may still not be ordered.
E.g. consider the time list [0,3,1,2]