Copyright | (c) Henning Thielemann 2007-2010 |
---|---|
Maintainer | haskell@henning-thielemann.de |
Stability | stable |
Portability | Haskell 98 |
Safe Haskell | Safe |
Language | Haskell98 |
Event lists starting with a time difference and ending with a time difference.
- 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
- unzip :: T time (body0, body1) -> (T time body0, T time body1)
- 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 :: C 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 :: (Ord time, Num 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, Num 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 :: C time => (body -> Bool) -> T time body -> T time body
- partition :: C time => (body -> Bool) -> T time body -> (T time body, T time body)
- partitionMaybe :: C time => (body0 -> Maybe body1) -> T time body0 -> (T time body1, T time body0)
- partitionMaybeR :: C time => (body0 -> Maybe body1) -> T time body0 -> (T time body1, T time body0)
- slice :: (Eq a, C time) => (body -> a) -> T time body -> [(a, T time body)]
- foldr :: (time -> a -> b) -> (body -> b -> a) -> a -> T time body -> b
- foldl :: (a -> time -> b) -> (b -> body -> 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 :: C time => (body0 -> Maybe body1) -> T time body0 -> T time body1
- catMaybes :: C time => T time (Maybe body) -> T time body
- catMaybesR :: C 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
- reverse :: 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
- forceTimeHead :: C 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 :: C 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
Functor (T time) Source | |
Foldable (T time) Source | |
Traversable (T time) Source | |
(Eq time, Eq body) => Eq (T time body) Source | |
(Ord time, Ord body) => Ord (T time body) Source | |
(Show time, Show body) => Show (T time body) Source | |
(Arbitrary time, Arbitrary body) => Arbitrary (T time body) Source | |
C time => Monoid (T time 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
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 :: (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.
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.
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.
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
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.
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
Cf. catMaybesR
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.
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.
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.
cycleNaive :: C time => 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)
forceTimeHead :: C time => T time body -> T time body Source
collectCoincident :: C time => T time body -> T time [body] Source
mapCoincident :: C time => ([a] -> [b]) -> T time a -> T time b Source
toAbsoluteEventList :: Num time => time -> T time body -> T time body Source
fromAbsoluteEventList :: Num time => T time body -> T time body Source