time-domain-0.1.0.3: A library for time domains and durations
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.TimeDomain

Description

This module defines the TimeDomain class. Its instances model time, simulated and realtime. Several instances such as UTCTime, Double and Integer are supplied here.

Synopsis

Documentation

newtype NumTimeDomain a Source #

Any Num can be wrapped to form a TimeDomain.

Constructors

NumTimeDomain 

Fields

class TimeDifference d where Source #

A type of durations, or differences betweens time stamps.

Expected laws:

Methods

difference :: d -> d -> d Source #

Calculate the difference between two durations, compatibly with diffTime.

add :: d -> d -> d Source #

Add two time differences.

Instances

Instances details
TimeDifference Integer Source # 
Instance details

Defined in Data.TimeDomain

TimeDifference () Source # 
Instance details

Defined in Data.TimeDomain

Methods

difference :: () -> () -> () Source #

add :: () -> () -> () Source #

TimeDifference Double Source # 
Instance details

Defined in Data.TimeDomain

TimeDifference Float Source # 
Instance details

Defined in Data.TimeDomain

Num a => TimeDifference (NumTimeDomain a) Source # 
Instance details

Defined in Data.TimeDomain

class TimeDifference (Diff time) => TimeDomain time where Source #

A time domain is an affine space representing a notion of time, such as real time, simulated time, steps, or a completely different notion.

Expected laws:

Associated Types

type Diff time Source #

The type of differences or durations between two timestamps

Methods

diffTime :: time -> time -> Diff time Source #

Compute the difference between two timestamps.

Mnemonic: diffTime behaves like the (-) operator:

diffTime earlier later = later `diffTime` earlier is the duration it takes from earlier to later.

addTime :: time -> Diff time -> time Source #

Add a time difference to a timestamp.

Instances

Instances details
TimeDomain UTCTime Source #

Differences between UTCTimes are measured in seconds.

Instance details

Defined in Data.TimeDomain

Associated Types

type Diff UTCTime Source #

TimeDomain Integer Source # 
Instance details

Defined in Data.TimeDomain

Associated Types

type Diff Integer Source #

TimeDomain () Source # 
Instance details

Defined in Data.TimeDomain

Associated Types

type Diff () Source #

Methods

diffTime :: () -> () -> Diff () Source #

addTime :: () -> Diff () -> () Source #

TimeDomain Double Source # 
Instance details

Defined in Data.TimeDomain

Associated Types

type Diff Double Source #

TimeDomain Float Source # 
Instance details

Defined in Data.TimeDomain

Associated Types

type Diff Float Source #

Num a => TimeDomain (NumTimeDomain a) Source # 
Instance details

Defined in Data.TimeDomain

Associated Types

type Diff (NumTimeDomain a) Source #

data UTCTime #

This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.

Instances

Instances details
Data UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UTCTime -> c UTCTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UTCTime #

toConstr :: UTCTime -> Constr #

dataTypeOf :: UTCTime -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> UTCTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UTCTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

NFData UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

rnf :: UTCTime -> () #

Eq UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

(==) :: UTCTime -> UTCTime -> Bool #

(/=) :: UTCTime -> UTCTime -> Bool #

Ord UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

TimeDomain UTCTime Source #

Differences between UTCTimes are measured in seconds.

Instance details

Defined in Data.TimeDomain

Associated Types

type Diff UTCTime Source #

type Diff UTCTime Source # 
Instance details

Defined in Data.TimeDomain