netwire-5.0.3: Functional reactive programming library

Copyright(c) 2013 Ertugrul Soeylemez
LicenseBSD3
MaintainerErtugrul Soeylemez <es@ertes.de>
Safe HaskellSafe
LanguageHaskell2010

FRP.Netwire.Utils.Timeline

Contents

Description

 

Synopsis

Time lines for statistics wires

data Timeline t a Source #

A time line is a non-empty set of samples together with time information.

Instances

Functor (Timeline t) Source # 

Methods

fmap :: (a -> b) -> Timeline t a -> Timeline t b #

(<$) :: a -> Timeline t b -> Timeline t a #

(Eq a, Eq t) => Eq (Timeline t a) Source # 

Methods

(==) :: Timeline t a -> Timeline t a -> Bool #

(/=) :: Timeline t a -> Timeline t a -> Bool #

(Ord t, Data a, Data t) => Data (Timeline t a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Timeline t a -> c (Timeline t a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Timeline t a) #

toConstr :: Timeline t a -> Constr #

dataTypeOf :: Timeline t a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Timeline t a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Timeline t a)) #

gmapT :: (forall b. Data b => b -> b) -> Timeline t a -> Timeline t a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Timeline t a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Timeline t a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Timeline t a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Timeline t a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Timeline t a -> m (Timeline t a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Timeline t a -> m (Timeline t a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Timeline t a -> m (Timeline t a) #

(Ord a, Ord t) => Ord (Timeline t a) Source # 

Methods

compare :: Timeline t a -> Timeline t a -> Ordering #

(<) :: Timeline t a -> Timeline t a -> Bool #

(<=) :: Timeline t a -> Timeline t a -> Bool #

(>) :: Timeline t a -> Timeline t a -> Bool #

(>=) :: Timeline t a -> Timeline t a -> Bool #

max :: Timeline t a -> Timeline t a -> Timeline t a #

min :: Timeline t a -> Timeline t a -> Timeline t a #

(Read a, Read t, Ord t) => Read (Timeline t a) Source # 
(Show a, Show t) => Show (Timeline t a) Source # 

Methods

showsPrec :: Int -> Timeline t a -> ShowS #

show :: Timeline t a -> String #

showList :: [Timeline t a] -> ShowS #

Constructing time lines

insert :: Ord t => t -> a -> Timeline t a -> Timeline t a Source #

Insert the given data point.

singleton :: t -> a -> Timeline t a Source #

Singleton timeline with the given point.

union :: Ord t => Timeline t a -> Timeline t a -> Timeline t a Source #

Union of two time lines. Right-biased.

Linear sampling

linAvg :: (Fractional a, Fractional t, Real t) => t -> t -> Timeline t a -> a Source #

Linearly interpolate the points in the time line, integrate the given time interval of the graph, divide by the interval length.

linCutL :: (Fractional a, Fractional t, Real t) => t -> Timeline t a -> Timeline t a Source #

Cut the timeline at the given point in time t, such that all samples up to but not including t are forgotten. The most recent sample before t is moved and interpolated accordingly.

linCutR :: (Fractional a, Fractional t, Real t) => t -> Timeline t a -> Timeline t a Source #

Cut the timeline at the given point in time t, such that all samples later than t are forgotten. The most recent sample after t is moved and interpolated accordingly.

linLookup :: (Fractional a, Fractional t, Real t) => t -> Timeline t a -> a Source #

Look up with linear sampling.

Staircase sampling

scAvg :: (Fractional a, Real t) => t -> t -> Timeline t a -> a Source #

Integrate the given time interval of the staircase, divide by the interval length.

scCutL :: Ord t => t -> Timeline t a -> Timeline t a Source #

Cut the timeline at the given point in time t, such that all samples up to but not including t are forgotten. The most recent sample before t is moved accordingly.

scCutR :: Ord t => t -> Timeline t a -> Timeline t a Source #

Cut the timeline at the given point in time t, such that all samples later than t are forgotten. The earliest sample after t is moved accordingly.

scLookup :: Ord t => t -> Timeline t a -> a Source #

Look up on staircase.