fuzzy-time-0.0.0.0

Safe HaskellNone
LanguageHaskell2010

Data.FuzzyTime.Types

Documentation

data FuzzyZonedTime Source #

Constructors

ZonedNow 
Instances
Eq FuzzyZonedTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Show FuzzyZonedTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Generic FuzzyZonedTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Associated Types

type Rep FuzzyZonedTime :: Type -> Type #

NFData FuzzyZonedTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: FuzzyZonedTime -> () #

Validity FuzzyZonedTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

type Rep FuzzyZonedTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

type Rep FuzzyZonedTime = D1 (MetaData "FuzzyZonedTime" "Data.FuzzyTime.Types" "fuzzy-time-0.0.0.0-I2DdKGvZtPCDTaydQTaa37" False) (C1 (MetaCons "ZonedNow" PrefixI False) (U1 :: Type -> Type))

data AmbiguousLocalTime Source #

newtype FuzzyLocalTime Source #

Instances
Eq FuzzyLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Show FuzzyLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Generic FuzzyLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Associated Types

type Rep FuzzyLocalTime :: Type -> Type #

NFData FuzzyLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: FuzzyLocalTime -> () #

Validity FuzzyLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

type Rep FuzzyLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

type Rep FuzzyLocalTime = D1 (MetaData "FuzzyLocalTime" "Data.FuzzyTime.Types" "fuzzy-time-0.0.0.0-I2DdKGvZtPCDTaydQTaa37" True) (C1 (MetaCons "FuzzyLocalTime" PrefixI True) (S1 (MetaSel (Just "unFuzzyLocalTime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Some FuzzyDay FuzzyTimeOfDay))))

data Some a b Source #

Constructors

One a 
Other b 
Both a b 
Instances
(Eq a, Eq b) => Eq (Some a b) Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

(==) :: Some a b -> Some a b -> Bool #

(/=) :: Some a b -> Some a b -> Bool #

(Show a, Show b) => Show (Some a b) Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

showsPrec :: Int -> Some a b -> ShowS #

show :: Some a b -> String #

showList :: [Some a b] -> ShowS #

Generic (Some a b) Source # 
Instance details

Defined in Data.FuzzyTime.Types

Associated Types

type Rep (Some a b) :: Type -> Type #

Methods

from :: Some a b -> Rep (Some a b) x #

to :: Rep (Some a b) x -> Some a b #

(NFData a, NFData b) => NFData (Some a b) Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: Some a b -> () #

(Validity a, Validity b) => Validity (Some a b) Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

validate :: Some a b -> Validation #

type Rep (Some a b) Source # 
Instance details

Defined in Data.FuzzyTime.Types

data FuzzyTimeOfDay Source #

Instances
Eq FuzzyTimeOfDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

Show FuzzyTimeOfDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

Generic FuzzyTimeOfDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

Associated Types

type Rep FuzzyTimeOfDay :: Type -> Type #

NFData FuzzyTimeOfDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: FuzzyTimeOfDay -> () #

Validity FuzzyTimeOfDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

type Rep FuzzyTimeOfDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

data FuzzyDay Source #

Instances
Eq FuzzyDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

Show FuzzyDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

Generic FuzzyDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

Associated Types

type Rep FuzzyDay :: Type -> Type #

Methods

from :: FuzzyDay -> Rep FuzzyDay x #

to :: Rep FuzzyDay x -> FuzzyDay #

NFData FuzzyDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: FuzzyDay -> () #

Validity FuzzyDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

type Rep FuzzyDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

type Rep FuzzyDay = D1 (MetaData "FuzzyDay" "Data.FuzzyTime.Types" "fuzzy-time-0.0.0.0-I2DdKGvZtPCDTaydQTaa37" False) (((C1 (MetaCons "Yesterday" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Now" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Today" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Tomorrow" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OnlyDay" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))) :+: ((C1 (MetaCons "DayInMonth" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: (C1 (MetaCons "DiffDays" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int16)) :+: C1 (MetaCons "DiffWeeks" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int16)))) :+: (C1 (MetaCons "DiffMonths" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int16)) :+: (C1 (MetaCons "NextDayOfTheWeek" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DayOfTheWeek)) :+: C1 (MetaCons "ExactDay" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Day))))))

data DayOfTheWeek Source #

Instances
Bounded DayOfTheWeek Source # 
Instance details

Defined in Data.FuzzyTime.Types

Enum DayOfTheWeek Source # 
Instance details

Defined in Data.FuzzyTime.Types

Eq DayOfTheWeek Source # 
Instance details

Defined in Data.FuzzyTime.Types

Show DayOfTheWeek Source # 
Instance details

Defined in Data.FuzzyTime.Types

Generic DayOfTheWeek Source # 
Instance details

Defined in Data.FuzzyTime.Types

Associated Types

type Rep DayOfTheWeek :: Type -> Type #

NFData DayOfTheWeek Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: DayOfTheWeek -> () #

Validity DayOfTheWeek Source # 
Instance details

Defined in Data.FuzzyTime.Types

type Rep DayOfTheWeek Source # 
Instance details

Defined in Data.FuzzyTime.Types

type Rep DayOfTheWeek = D1 (MetaData "DayOfTheWeek" "Data.FuzzyTime.Types" "fuzzy-time-0.0.0.0-I2DdKGvZtPCDTaydQTaa37" False) ((C1 (MetaCons "Monday" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Tuesday" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Wednesday" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Thursday" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Friday" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Saturday" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Sunday" PrefixI False) (U1 :: Type -> Type))))

data Month Source #

Instances
Bounded Month Source # 
Instance details

Defined in Data.FuzzyTime.Types

Enum Month Source # 
Instance details

Defined in Data.FuzzyTime.Types

Eq Month Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

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

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

Show Month Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

showsPrec :: Int -> Month -> ShowS #

show :: Month -> String #

showList :: [Month] -> ShowS #

Generic Month Source # 
Instance details

Defined in Data.FuzzyTime.Types

Associated Types

type Rep Month :: Type -> Type #

Methods

from :: Month -> Rep Month x #

to :: Rep Month x -> Month #

NFData Month Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: Month -> () #

Validity Month Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

validate :: Month -> Validation #

type Rep Month Source # 
Instance details

Defined in Data.FuzzyTime.Types

type Rep Month = D1 (MetaData "Month" "Data.FuzzyTime.Types" "fuzzy-time-0.0.0.0-I2DdKGvZtPCDTaydQTaa37" False) (((C1 (MetaCons "January" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "February" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "March" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "April" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "May" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "June" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "July" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "August" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "September" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "October" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "November" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "December" PrefixI False) (U1 :: Type -> Type)))))