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 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.
- 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 :: C time => T time body -> time
- 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] -> 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)
- foldr :: (time -> a -> b) -> (body -> b -> a) -> b -> T time body -> b
- foldrPair :: (time -> body -> a -> a) -> a -> T time body -> a
- 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
- insertBy :: C 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 :: 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)
- slice :: (Eq a, C time) => (body -> a) -> T time body -> [(a, T time body)]
- span :: (body -> Bool) -> T time body -> (T time body, T time body)
- mapMaybe :: C time => (body0 -> Maybe body1) -> T time body0 -> T time body1
- catMaybes :: C time => T time (Maybe body) -> T time body
- normalize :: (C time, Ord body) => T time body -> T time body
- isNormalized :: (C time, Ord body) => T time body -> Bool
- 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
- append :: T time body -> T time body -> T time body
- concat :: [T time body] -> T time body
- cycle :: 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
- toAbsoluteEventList :: Num time => time -> T time body -> T time body
- fromAbsoluteEventList :: Num time => T time body -> T time body
- toAbsoluteEventListGen :: (absTime -> relTime -> absTime) -> absTime -> T relTime body -> T absTime body
- fromAbsoluteEventListGen :: (absTime -> absTime -> relTime) -> absTime -> T absTime body -> T relTime 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 time, Show body) => Show (T time body) Source # | |
Semigroup (T time body) Source # | |
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 #
zipWithBody :: (body0 -> body1 -> body2) -> [body0] -> T time body1 -> T time body2 Source #
zipWithTime :: (time0 -> time1 -> time2) -> [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 #
This function merges the events of two lists into a new event list.
Note that merge
compares entire events rather than just start times.
This is to ensure that it is commutative,
one of the properties we test for.
mergeBy :: C time => (body -> body -> Bool) -> T time body -> T time body -> T time body Source #
mergeBy
is like merge
but does not simply use the methods of the Ord
class
but allows a custom comparison function.
If in event lists xs
and ys
there are coinciding elements x
and y
,
and cmp x y
is True
,
then x
comes before y
in mergeBy cmp xs ys
.
EventList> EventList.mergeBy (\_ _ -> True) (0 /. 'a' ./ empty) (0 /. 'b' ./ empty) 0 /. 'a' ./ 0 /. 'b' ./ empty EventList> EventList.mergeBy (\_ _ -> False) (0 /. 'a' ./ empty) (0 /. 'b' ./ empty) 0 /. 'b' ./ 0 /. 'a' ./ empty
insert :: (C time, Ord body) => time -> body -> T time body -> T time body Source #
insert
inserts an event into an event list at the given time.
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.
filter :: C time => (body -> Bool) -> T time body -> T time body Source #
Keep only events that match a predicate while preserving absolute times.
partitionMaybe :: 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 #
Using a classification function we splice the event list into lists, each containing the same class. Absolute time stamps are preserved.
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.
collectCoincident :: C time => T time body -> T time [body] Source #
Group events that have equal start times (that is zero time differences).
flatten :: C time => T time [body] -> T time body Source #
Reverse to collectCoincident:
Turn each body
into a separate event.
xs == flatten (collectCoincident xs)
mapCoincident :: C time => ([a] -> [b]) -> T time a -> T time b Source #
Apply a function to the lists of coincident events.
discretize :: (C time, RealFrac time, C i, Integral i) => T time body -> T i body Source #
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 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.
toAbsoluteEventList :: Num time => time -> T time body -> T time body Source #
We tried hard to compute everything with respect to relative times. However sometimes we need absolute time values.
toAbsoluteEventListGen :: (absTime -> relTime -> absTime) -> absTime -> T relTime body -> T absTime body Source #
Convert from relative time stamps to absolute time stamps
using a custom accumulator function (like (+)
).
fromAbsoluteEventListGen :: (absTime -> absTime -> relTime) -> absTime -> T absTime body -> T relTime body Source #
Convert from absolute time stamps to relative time stamps
using custom subtraction (like (-)
) and zero.