hora-2.2.0: date time

Safe HaskellNone
LanguageHaskell2010

Data.Time.Hora.Type

Contents

Synopsis

DatePart

data DatePart a Source #

serializeable structure for essential Date, Time parts

may also be used to construct UTCTime

see Data.Time.Hora.Part for conversion between UTCTime and DatePart

Constructors

DatePart 

Fields

Instances
Functor DatePart Source #

for ease of conversion

Instance details

Defined in Data.Time.Hora.Type

Methods

fmap :: (a -> b) -> DatePart a -> DatePart b #

(<$) :: a -> DatePart b -> DatePart a #

Eq a => Eq (DatePart a) Source # 
Instance details

Defined in Data.Time.Hora.Type

Methods

(==) :: DatePart a -> DatePart a -> Bool #

(/=) :: DatePart a -> DatePart a -> Bool #

Ord a => Ord (DatePart a) Source # 
Instance details

Defined in Data.Time.Hora.Type

Methods

compare :: DatePart a -> DatePart a -> Ordering #

(<) :: DatePart a -> DatePart a -> Bool #

(<=) :: DatePart a -> DatePart a -> Bool #

(>) :: DatePart a -> DatePart a -> Bool #

(>=) :: DatePart a -> DatePart a -> Bool #

max :: DatePart a -> DatePart a -> DatePart a #

min :: DatePart a -> DatePart a -> DatePart a #

Show a => Show (DatePart a) Source # 
Instance details

Defined in Data.Time.Hora.Type

Methods

showsPrec :: Int -> DatePart a -> ShowS #

show :: DatePart a -> String #

showList :: [DatePart a] -> ShowS #

Generic (DatePart a) Source # 
Instance details

Defined in Data.Time.Hora.Type

Associated Types

type Rep (DatePart a) :: * -> * #

Methods

from :: DatePart a -> Rep (DatePart a) x #

to :: Rep (DatePart a) x -> DatePart a #

Binary (DatePart Int) Source #

serializeable

Instance details

Defined in Data.Time.Hora.Type

Binary (DatePart Integer) Source #

serializeable

Instance details

Defined in Data.Time.Hora.Type

Binary (DatePart String) Source #

serializeable

Instance details

Defined in Data.Time.Hora.Type

Integral a => ToUTC (Tz (DatePart a)) Source # 
Instance details

Defined in Data.Time.Hora.Part

Methods

toUtc :: Tz (DatePart a) -> Maybe UTCTime Source #

Integral a => ToUTC (DatePart a) Source #

assumes DatePart is UTC

Instance details

Defined in Data.Time.Hora.Part

Integral a => FromUTC (DatePart a) Source #

returns DatePart a in UTC timezone

Instance details

Defined in Data.Time.Hora.Part

Integral a => Now (Tz (DatePart a)) Source #

local timezone

Tz (DatePart a) parts show local date & time

>>> now::IO(Tz (DatePart Int))
Tz CET (DatePart {year = 2016, month = 12, day = 15, hour = 11, minute = 21, second = 21, pico = 657029375000})     
Instance details

Defined in Data.Time.Hora.Stamp

Methods

now :: IO (Tz (DatePart a)) Source #

Integral a => Now (DatePart a) Source #

UTC

>>> now::IO(DatePart Int)
DatePart {year = 2016, month = 12, day = 15, hour = 10, minute = 20, second = 31, pico = 494880242000}
Instance details

Defined in Data.Time.Hora.Stamp

Methods

now :: IO (DatePart a) Source #

type Rep (DatePart a) Source # 
Instance details

Defined in Data.Time.Hora.Type

DatePartSmall

data DatePartSmall Source #

DatePartSmall uses fixed-size storage. Storage (as encoded with Data.Binary.encode) varies with the constructor used, is noted as ".. bytes" against each constructor.

allows to operate with dates only ..

.. or time (minute / millisecond precision) only

is convenient for dealing with intervals / timespans

day count begins at 1 Jan 0001: 1 Jan 0001 is day 1

max date is: 11759222-01-19. That's 19 Jan 11759222

see Data.Time.Hora.Part for conversion between UTCTime and DatePartSmall

only values constructed with DatePartSmall can be converted to UTCTime

Constructors

Day Word32

days after 31 Dec 1 BC: 1 Jan AD 1 is day 1. See https://en.wikipedia.org/wiki/Anno_Domini

5 bytes

Min Word16

minutes (includes hours)

3 bytes

Ms Word32

milliseconds (includes seconds)

5 bytes

Time Word16 Word32

minutes, milliseconds

7 bytes

DatePartSmall Word32 Word16 Word32

date, minutes, milliseconds

11 bytes

Day' Word32

date span in days

5 bytes

Min' Word16

time span in minutes

3 bytes

Ms' Word32

time span in milliseconds

5 bytes

Error ErrorDetail

result of failed operation

Instances
Eq DatePartSmall Source # 
Instance details

Defined in Data.Time.Hora.Internal.DatePartSmall

Show DatePartSmall Source # 
Instance details

Defined in Data.Time.Hora.Internal.DatePartSmall

Generic DatePartSmall Source # 
Instance details

Defined in Data.Time.Hora.Internal.DatePartSmall

Associated Types

type Rep DatePartSmall :: * -> * #

Semigroup DatePartSmall Source #

<> can be used both to combine parts (e.g. Day, Time) and to add date/time span to the existing parts

combining parts:

Day <> Time -> DatePartSmall

>>> show' (mkDay 2018 08 20 <> mkMin 10 2 <> mkMs 30 9)
2018-08-20 10:02:30.009

Min <> Ms -> Time

adding span:

Day <> Day' -> Day

>>> show' (mkDay 2018 1 1 <> Day' 20)
2018-01-21
>>> show' (mkDay 2018 1 1 <> Day' 180)
2018-06-30

Min <> Min' -> Min

>>> show' (mkMin 3 15 <> Min' 200)
06:35

Ms <> Ms' -> Ms

>>> show' $ normalize $ mkMin 14 59 <> mkMs 132 9 <> Ms' 5308
15:01:17.317

when incrementing and decrementing, overflow is checked on both upper (max for Word16, Word32) and lower (0) bounds

when incrementing, it is possible to normalize time by recalculating minutes from seconds, days from minutes. See normalize in Data.Time.Hora.Part

when decrementing, normalization is not yet implemented. todo

Instance details

Defined in Data.Time.Hora.Internal.DatePartSmall

Binary DatePartSmall Source # 
Instance details

Defined in Data.Time.Hora.Internal.DatePartSmall

ToUTC DatePartSmall Source # 
Instance details

Defined in Data.Time.Hora.Part

FromUTC DatePartSmall Source # 
Instance details

Defined in Data.Time.Hora.Part

type Rep DatePartSmall Source # 
Instance details

Defined in Data.Time.Hora.Internal.DatePartSmall

type Rep DatePartSmall = D1 (MetaData "DatePartSmall" "Data.Time.Hora.Internal.DatePartSmall" "hora-2.2.0-LsHHjglBktYDfEE6VgilWA" False) (((C1 (MetaCons "Day" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)) :+: C1 (MetaCons "Min" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word16))) :+: (C1 (MetaCons "Ms" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)) :+: (C1 (MetaCons "Time" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word16) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)) :+: C1 (MetaCons "DatePartSmall" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word16) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))))) :+: ((C1 (MetaCons "Day'" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)) :+: C1 (MetaCons "Min'" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word16))) :+: (C1 (MetaCons "Ms'" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)) :+: (C1 (MetaCons "Neg" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DatePartSmall)) :+: C1 (MetaCons "Error" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ErrorDetail))))))

toSpan :: DatePartSmall -> DatePartSmall Source #

substitutes constructor:

Day -> Day'

Min -> Min'

Ms -> Ms'

negate :: DatePartSmall -> DatePartSmall Source #

adds hidden Neg constructor to Day', Min' or Ms' to enable negative spans

isNegative :: DatePartSmall -> Bool Source #

checks if DatePartSmall is a negative span

data ErrorDetail Source #

Constructors

Invalid

operation is not possible with these constructors

Overflow

data type maxed out

Invalid_Overflow

Invalid <> Overflow

Instances
Eq ErrorDetail Source # 
Instance details

Defined in Data.Time.Hora.Internal.DatePartSmall

Show ErrorDetail Source # 
Instance details

Defined in Data.Time.Hora.Internal.DatePartSmall

Generic ErrorDetail Source # 
Instance details

Defined in Data.Time.Hora.Internal.DatePartSmall

Associated Types

type Rep ErrorDetail :: * -> * #

Binary ErrorDetail Source # 
Instance details

Defined in Data.Time.Hora.Internal.DatePartSmall

type Rep ErrorDetail Source # 
Instance details

Defined in Data.Time.Hora.Internal.DatePartSmall

type Rep ErrorDetail = D1 (MetaData "ErrorDetail" "Data.Time.Hora.Internal.DatePartSmall" "hora-2.2.0-LsHHjglBktYDfEE6VgilWA" False) (C1 (MetaCons "Invalid" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Overflow" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Invalid_Overflow" PrefixI False) (U1 :: * -> *)))

UTCTimeBin

data UTCTimeBin Source #

UTCTimeBin closely mimicks UTCTime without loss of precision

UTCTimeBin has Binary instance. The only purpose of UTCTimeBin is to offer faster conversion from / to UTCTime and more compact serialization compared with DatePart.

see Data.Time.Hora.Part for conversion between UTCTime and UTCTimeBin

Constructors

UTCTimeBin 

Fields

Instances
Eq UTCTimeBin Source # 
Instance details

Defined in Data.Time.Hora.Type

Show UTCTimeBin Source # 
Instance details

Defined in Data.Time.Hora.Type

Generic UTCTimeBin Source # 
Instance details

Defined in Data.Time.Hora.Type

Associated Types

type Rep UTCTimeBin :: * -> * #

Binary UTCTimeBin Source #

serializeable

Instance details

Defined in Data.Time.Hora.Type

ToUTC UTCTimeBin Source # 
Instance details

Defined in Data.Time.Hora.Part

FromUTC UTCTimeBin Source # 
Instance details

Defined in Data.Time.Hora.Part

type Rep UTCTimeBin Source # 
Instance details

Defined in Data.Time.Hora.Type

type Rep UTCTimeBin = D1 (MetaData "UTCTimeBin" "Data.Time.Hora.Type" "hora-2.2.0-LsHHjglBktYDfEE6VgilWA" False) (C1 (MetaCons "UTCTimeBin" PrefixI True) (S1 (MetaSel (Just "modifiedJulianDay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer) :*: S1 (MetaSel (Just "diffTimeAsPicoseconds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

Tz

data Tz a Source #

Tz (DatePart a) parts show local date & time

for conversions between timezones see Data.Time.Hora.Zone

Constructors

Tz TimeZone a 
Instances
Functor Tz Source # 
Instance details

Defined in Data.Time.Hora.Type

Methods

fmap :: (a -> b) -> Tz a -> Tz b #

(<$) :: a -> Tz b -> Tz a #

Eq a => Eq (Tz a) Source # 
Instance details

Defined in Data.Time.Hora.Type

Methods

(==) :: Tz a -> Tz a -> Bool #

(/=) :: Tz a -> Tz a -> Bool #

Ord a => Ord (Tz a) Source # 
Instance details

Defined in Data.Time.Hora.Type

Methods

compare :: Tz a -> Tz a -> Ordering #

(<) :: Tz a -> Tz a -> Bool #

(<=) :: Tz a -> Tz a -> Bool #

(>) :: Tz a -> Tz a -> Bool #

(>=) :: Tz a -> Tz a -> Bool #

max :: Tz a -> Tz a -> Tz a #

min :: Tz a -> Tz a -> Tz a #

Show a => Show (Tz a) Source # 
Instance details

Defined in Data.Time.Hora.Type

Methods

showsPrec :: Int -> Tz a -> ShowS #

show :: Tz a -> String #

showList :: [Tz a] -> ShowS #

Integral a => ToUTC (Tz (DatePart a)) Source # 
Instance details

Defined in Data.Time.Hora.Part

Methods

toUtc :: Tz (DatePart a) -> Maybe UTCTime Source #

Timestamp (Tz String) Source #

local timezone

Instance details

Defined in Data.Time.Hora.Stamp

Methods

ts :: [Format] -> IO (Tz String) Source #

Integral a => Now (Tz (DatePart a)) Source #

local timezone

Tz (DatePart a) parts show local date & time

>>> now::IO(Tz (DatePart Int))
Tz CET (DatePart {year = 2016, month = 12, day = 15, hour = 11, minute = 21, second = 21, pico = 657029375000})     
Instance details

Defined in Data.Time.Hora.Stamp

Methods

now :: IO (Tz (DatePart a)) Source #

class Tz' tz where Source #

Minimal complete definition

tz'

Methods

tz' :: tz -> UTCTime -> TimeZone Source #

Instances
Tz' TimeZone Source # 
Instance details

Defined in Data.Time.Hora.Type

Tz' TimeZoneSeries Source #

see Data.Time.Hora.Zone re: TimeZoneSeries

use of TimeZoneSeries is preferred when converting from UTCTime to DatePart

Instance details

Defined in Data.Time.Hora.Type

TimeSpan

data TimeSpan a Source #

second and fractions

see Data.Time.Hora.Span for conversion

Constructors

Sec a 
Pico a 
Milli a 
Instances
Functor TimeSpan Source # 
Instance details

Defined in Data.Time.Hora.Internal.Span

Methods

fmap :: (a -> b) -> TimeSpan a -> TimeSpan b #

(<$) :: a -> TimeSpan b -> TimeSpan a #

(Eq a, Integral a) => Eq (TimeSpan a) #
>>> Sec 1 == Milli 1000
True    
Instance details

Defined in Data.Time.Hora.Type

Methods

(==) :: TimeSpan a -> TimeSpan a -> Bool #

(/=) :: TimeSpan a -> TimeSpan a -> Bool #

Integral a => Num (TimeSpan a) #

! fromInteger returns Pico. assumes the value is Pico seconds

>>> Milli 397100 + (Sec 2) + 37891470000
Pico 399137891470000
>>> Milli 397100 + (Sec 2) + (Pico 37891470000)
Pico 399137891470000
>>> 3 * (Sec 10) == (Sec 30)
True  
>>> 3 * (Pico 10) == (Pico 30)
True        
>>> 300 * (Milli 1000) == (Milli 300000)
True    
Instance details

Defined in Data.Time.Hora.Type

(Ord a, Integral a) => Ord (TimeSpan a) #
>>> Sec 1 > Milli 500
True        
Instance details

Defined in Data.Time.Hora.Type

Methods

compare :: TimeSpan a -> TimeSpan a -> Ordering #

(<) :: TimeSpan a -> TimeSpan a -> Bool #

(<=) :: TimeSpan a -> TimeSpan a -> Bool #

(>) :: TimeSpan a -> TimeSpan a -> Bool #

(>=) :: TimeSpan a -> TimeSpan a -> Bool #

max :: TimeSpan a -> TimeSpan a -> TimeSpan a #

min :: TimeSpan a -> TimeSpan a -> TimeSpan a #

Show a => Show (TimeSpan a) Source # 
Instance details

Defined in Data.Time.Hora.Internal.Span

Methods

showsPrec :: Int -> TimeSpan a -> ShowS #

show :: TimeSpan a -> String #

showList :: [TimeSpan a] -> ShowS #

type TwoInt a b = (Integral a, Integral b) Source #

constraint

Orphan instances

(Eq a, Integral a) => Eq (TimeSpan a) Source #
>>> Sec 1 == Milli 1000
True    
Instance details

Methods

(==) :: TimeSpan a -> TimeSpan a -> Bool #

(/=) :: TimeSpan a -> TimeSpan a -> Bool #

Integral a => Num (TimeSpan a) Source #

! fromInteger returns Pico. assumes the value is Pico seconds

>>> Milli 397100 + (Sec 2) + 37891470000
Pico 399137891470000
>>> Milli 397100 + (Sec 2) + (Pico 37891470000)
Pico 399137891470000
>>> 3 * (Sec 10) == (Sec 30)
True  
>>> 3 * (Pico 10) == (Pico 30)
True        
>>> 300 * (Milli 1000) == (Milli 300000)
True    
Instance details

(Ord a, Integral a) => Ord (TimeSpan a) Source #
>>> Sec 1 > Milli 500
True        
Instance details

Methods

compare :: TimeSpan a -> TimeSpan a -> Ordering #

(<) :: TimeSpan a -> TimeSpan a -> Bool #

(<=) :: TimeSpan a -> TimeSpan a -> Bool #

(>) :: TimeSpan a -> TimeSpan a -> Bool #

(>=) :: TimeSpan a -> TimeSpan a -> Bool #

max :: TimeSpan a -> TimeSpan a -> TimeSpan a #

min :: TimeSpan a -> TimeSpan a -> TimeSpan a #