haskell-time-range-0.2.0.0: Some useful wrappers and functions for building time ranges

Safe HaskellNone
LanguageHaskell2010

Data.Time.Range.Types

Synopsis

Documentation

data StartDate Source #

General purpose newtype wrappers for some commonly used Data.Time types. Helps to ensure you don't get your range ends mixed up, as well as providing some convenience when you only need to refer to particular levels of granularity in the time range.

Initial need of this library was only at the day and hour level, if there is a need more granular times can be added.

Instances

Eq StartDate Source # 
Show StartDate Source # 
Generic StartDate Source # 

Associated Types

type Rep StartDate :: * -> * #

Wrapped StartDate Source # 

Associated Types

type Unwrapped StartDate :: * #

(~) * StartDate t0 => Rewrapped StartDate t0 Source # 
type Rep StartDate Source # 
type Rep StartDate = D1 (MetaData "StartDate" "Data.Time.Range.Types" "haskell-time-range-0.2.0.0-4QEnZRTH6YT9dyegXKvc4i" True) (C1 (MetaCons "StartDate" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Day)))
type Unwrapped StartDate Source # 

data EndDate Source #

Instances

Eq EndDate Source # 

Methods

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

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

Show EndDate Source # 
Generic EndDate Source # 

Associated Types

type Rep EndDate :: * -> * #

Methods

from :: EndDate -> Rep EndDate x #

to :: Rep EndDate x -> EndDate #

Wrapped EndDate Source # 

Associated Types

type Unwrapped EndDate :: * #

(~) * EndDate t0 => Rewrapped EndDate t0 Source # 
type Rep EndDate Source # 
type Rep EndDate = D1 (MetaData "EndDate" "Data.Time.Range.Types" "haskell-time-range-0.2.0.0-4QEnZRTH6YT9dyegXKvc4i" True) (C1 (MetaCons "EndDate" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Day)))
type Unwrapped EndDate Source # 

data DayInRange Source #

Instances

Eq DayInRange Source # 
Show DayInRange Source # 
Generic DayInRange Source # 

Associated Types

type Rep DayInRange :: * -> * #

Wrapped DayInRange Source # 

Associated Types

type Unwrapped DayInRange :: * #

(~) * DayInRange t0 => Rewrapped DayInRange t0 Source # 
type Rep DayInRange Source # 
type Rep DayInRange = D1 (MetaData "DayInRange" "Data.Time.Range.Types" "haskell-time-range-0.2.0.0-4QEnZRTH6YT9dyegXKvc4i" True) (C1 (MetaCons "DayInRange" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Day)))
type Unwrapped DayInRange Source # 

data StartHour Source #

Instances

Eq StartHour Source # 
Show StartHour Source # 
Generic StartHour Source # 

Associated Types

type Rep StartHour :: * -> * #

Wrapped StartHour Source # 

Associated Types

type Unwrapped StartHour :: * #

(~) * StartHour t0 => Rewrapped StartHour t0 Source # 
type Rep StartHour Source # 
type Rep StartHour = D1 (MetaData "StartHour" "Data.Time.Range.Types" "haskell-time-range-0.2.0.0-4QEnZRTH6YT9dyegXKvc4i" True) (C1 (MetaCons "StartHour" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural)))
type Unwrapped StartHour Source # 

data EndHour Source #

Instances

Eq EndHour Source # 

Methods

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

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

Show EndHour Source # 
Generic EndHour Source # 

Associated Types

type Rep EndHour :: * -> * #

Methods

from :: EndHour -> Rep EndHour x #

to :: Rep EndHour x -> EndHour #

Wrapped EndHour Source # 

Associated Types

type Unwrapped EndHour :: * #

(~) * EndHour t0 => Rewrapped EndHour t0 Source # 
type Rep EndHour Source # 
type Rep EndHour = D1 (MetaData "EndHour" "Data.Time.Range.Types" "haskell-time-range-0.2.0.0-4QEnZRTH6YT9dyegXKvc4i" True) (C1 (MetaCons "EndHour" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural)))
type Unwrapped EndHour Source # 

data Hour Source #

Instances

Eq Hour Source # 

Methods

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

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

Show Hour Source # 

Methods

showsPrec :: Int -> Hour -> ShowS #

show :: Hour -> String #

showList :: [Hour] -> ShowS #

Generic Hour Source # 

Associated Types

type Rep Hour :: * -> * #

Methods

from :: Hour -> Rep Hour x #

to :: Rep Hour x -> Hour #

Wrapped Hour Source # 

Associated Types

type Unwrapped Hour :: * #

(~) * Hour t0 => Rewrapped Hour t0 Source # 
type Rep Hour Source # 
type Rep Hour = D1 (MetaData "Hour" "Data.Time.Range.Types" "haskell-time-range-0.2.0.0-4QEnZRTH6YT9dyegXKvc4i" True) (C1 (MetaCons "Hour" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))
type Unwrapped Hour Source # 

data Ranges Source #