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

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

Data.EventList.Relative.BodyTime

Description

Event lists starting with a body and ending with a time difference.

Documentation

data T time body Source

Instances

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 
Monoid (T time body) Source 

empty :: T time body Source

singleton :: body -> time -> T time body Source

null :: T time body -> Bool Source

fromPairList :: [(body, time)] -> T time body Source

toPairList :: T time body -> [(body, time)] Source

getTimes :: T time body -> [time] Source

getBodies :: T time body -> [body] Source

duration :: Num time => T time body -> time Source

durationR :: Num time => T time body -> time 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

foldr :: (body -> a -> b) -> (time -> b -> a) -> b -> T time body -> b Source

foldrPair :: (body -> time -> a -> a) -> a -> T time body -> a Source

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

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

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

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

switchL :: c -> (body -> time -> T time body -> c) -> T time body -> c Source

switchR :: c -> (T time body -> body -> time -> c) -> T time body -> c Source

span :: (body -> Bool) -> T time body -> (T time body, T time body) Source