event-list-0.0.8: Event lists with relative or absolute time stampsSource codeContentsIndex
Data.EventList.Absolute.TimeTime
PortabilityHaskell 98
Stabilitystable
Maintainerhaskell@henning-thielemann.de
Description
Event list with absolute times starting with a time and ending with a body
Synopsis
data T time body
pause :: time -> T time body
isPause :: T time body -> Bool
viewL :: T time body -> (time, Maybe (body, T time body))
switchL :: (time -> a) -> ((time, body) -> T time body -> a) -> T time body -> a
cons :: time -> body -> T time body -> T time body
snoc :: T time body -> body -> time -> T time body
mapBody :: (body0 -> body1) -> T time body0 -> T time body1
mapTime :: (time0 -> time1) -> T time0 body -> 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 :: Num time => T time body -> time
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)
slice :: (Eq a, Num time) => (body -> a) -> T time body -> [(a, T time body)]
foldr :: (time -> a -> b) -> (body -> b -> a) -> a -> T time body -> b
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, Num time) => T time [body] -> T time body
mapCoincident :: (Ord time, Num 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
Documentation
data T time body Source
show/hide 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)
pause :: time -> T time bodySource
isPause :: T time body -> BoolSource
viewL :: T time body -> (time, Maybe (body, T time body))Source
switchL :: (time -> a) -> ((time, body) -> T time body -> a) -> T time body -> aSource
cons :: time -> body -> T time body -> T time bodySource
snoc :: T time body -> body -> time -> T time bodySource
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
getTimes :: T time body -> [time]Source
getBodies :: T time body -> [body]Source
duration :: Num time => T time body -> timeSource
merge :: (Ord time, Ord body) => T time body -> T time body -> T time bodySource
mergeBy :: Ord time => (body -> body -> Bool) -> T time body -> T time body -> T time bodySource
insert :: (Ord time, Ord body) => time -> body -> T time body -> T time bodySource
insertBy :: Ord time => (body -> body -> Bool) -> time -> body -> T time body -> T time bodySource
moveForward :: (Ord time, Num time) => T time (time, body) -> T time bodySource
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.
decreaseStart :: (Ord time, Num time) => time -> T time body -> T time bodySource
delay :: (Ord time, Num time) => time -> T time body -> T time bodySource
filter :: Num time => (body -> Bool) -> T time body -> T time bodySource
partition :: (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
foldr :: (time -> a -> b) -> (body -> b -> a) -> a -> T time body -> bSource
mapMaybe :: Num time => (body0 -> Maybe body1) -> T time body0 -> T time body1Source
catMaybes :: Num time => T time (Maybe body) -> T time bodySource
normalize :: (Ord time, Num 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 :: (Ord time, Num time, Ord body) => T time body -> BoolSource
collectCoincident :: Eq time => T time body -> T time [body]Source
flatten :: (Ord time, Num time) => T time [body] -> T time bodySource
mapCoincident :: (Ord time, Num time) => ([a] -> [b]) -> T time a -> T time bSource
Apply a function to the lists of coincident events.
append :: (Ord time, Num time) => T time body -> T time body -> T time bodySource
concat :: (Ord time, Num time) => [T time body] -> T time bodySource
cycle :: (Ord time, Num time) => T time body -> T time bodySource
discretize :: (RealFrac time, Integral i) => T time body -> T i bodySource
resample :: (RealFrac time, Integral i) => time -> T time body -> T i bodySource
Produced by Haddock version 2.4.2