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

Copyright(c) Henning Thielemann 2007-2009
Maintainerhaskell@henning-thielemann.de
Stabilitystable
PortabilityHaskell 98
Safe HaskellSafe
LanguageHaskell98

Data.EventList.Absolute.TimeTime

Description

Event list with absolute times starting with a time and ending with a body

Synopsis

Documentation

data T time body Source

Instances

(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 

pause :: time -> T time body Source

isPause :: T time body -> Bool Source

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

switchL :: (time -> a) -> ((time, body) -> T time body -> a) -> T time body -> a Source

cons :: time -> body -> T time body -> T time body Source

snoc :: T time body -> body -> time -> T time body Source

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

mapTime :: (time0 -> time1) -> T time0 body -> T time1 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

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 -> time Source

merge :: (Ord time, Ord body) => T time body -> T time body -> T time body Source

mergeBy :: Ord time => (body -> body -> Bool) -> T time body -> T time body -> T time body Source

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

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.

decreaseStart :: (Ord time, Num time) => time -> T time body -> T time body Source

delay :: (Ord time, Num time) => time -> T time body -> T time body Source

filter :: Num time => (body -> Bool) -> T time body -> T time body Source

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 -> b Source

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

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

normalize :: (Ord time, Num time, Ord body) => T time body -> T time body Source

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 -> Bool Source

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

flatten :: Ord time => T time [body] -> T time body Source

mapCoincident :: Ord time => ([a] -> [b]) -> T time a -> T time b Source

Apply a function to the lists of coincident events.

append :: (Ord time, Num time) => T time body -> T time body -> T time body Source

concat :: (Ord time, Num time) => [T time body] -> T time body Source

cycle :: (Ord time, Num time) => T time body -> T time body Source

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

resample :: (RealFrac time, Integral i) => time -> T time body -> T i body Source