fuzzy-time-0.2.0.1
Safe HaskellNone
LanguageHaskell2010

Data.FuzzyTime.Types

Documentation

data Month Source #

Instances

Instances details
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.2.0.1-Bsw5mng8iLGK1dbg8oUu2z" '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)))))

data FuzzyDay Source #

Instances

Instances details
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.2.0.1-Bsw5mng8iLGK1dbg8oUu2z" '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 DayOfWeek)) :+: C1 ('MetaCons "ExactDay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day))))))

data FuzzyTimeOfDay Source #

Instances

Instances details
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

type Rep FuzzyTimeOfDay = D1 ('MetaData "FuzzyTimeOfDay" "Data.FuzzyTime.Types" "fuzzy-time-0.2.0.1-Bsw5mng8iLGK1dbg8oUu2z" 'False) (((C1 ('MetaCons "SameTime" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Noon" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Midnight" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Morning" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Evening" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "AtHour" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "AtMinute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "AtExact" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeOfDay)))) :+: (C1 ('MetaCons "HoursDiff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "MinutesDiff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "SecondsDiff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pico))))))

data Some a b Source #

Constructors

One a 
Other b 
Both a b 

Instances

Instances details
(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

newtype FuzzyLocalTime Source #

Instances

Instances details
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.2.0.1-Bsw5mng8iLGK1dbg8oUu2z" 'True) (C1 ('MetaCons "FuzzyLocalTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "unFuzzyLocalTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Some FuzzyDay FuzzyTimeOfDay))))

data AmbiguousLocalTime Source #

Instances

Instances details
Eq AmbiguousLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Show AmbiguousLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Generic AmbiguousLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Associated Types

type Rep AmbiguousLocalTime :: Type -> Type #

NFData AmbiguousLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: AmbiguousLocalTime -> () #

Validity AmbiguousLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

type Rep AmbiguousLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

type Rep AmbiguousLocalTime = D1 ('MetaData "AmbiguousLocalTime" "Data.FuzzyTime.Types" "fuzzy-time-0.2.0.1-Bsw5mng8iLGK1dbg8oUu2z" 'False) (C1 ('MetaCons "OnlyDaySpecified" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)) :+: C1 ('MetaCons "BothTimeAndDay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalTime)))

data FuzzyZonedTime Source #

Constructors

ZonedNow 

Instances

Instances details
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.2.0.1-Bsw5mng8iLGK1dbg8oUu2z" 'False) (C1 ('MetaCons "ZonedNow" 'PrefixI 'False) (U1 :: Type -> Type))

data DayOfWeek #

Instances

Instances details
Enum DayOfWeek

"Circular", so for example [Tuesday ..] gives an endless sequence. Also: fromEnum gives [1 .. 7] for [Monday .. Sunday], and toEnum performs mod 7 to give a cycle of days.

Instance details

Defined in Data.Time.Calendar.Week

Eq DayOfWeek 
Instance details

Defined in Data.Time.Calendar.Week

Read DayOfWeek 
Instance details

Defined in Data.Time.Calendar.Week

Show DayOfWeek 
Instance details

Defined in Data.Time.Calendar.Week

Generic DayOfWeek Source # 
Instance details

Defined in Data.FuzzyTime.Types

Associated Types

type Rep DayOfWeek :: Type -> Type #

NFData DayOfWeek Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: DayOfWeek -> () #

type Rep DayOfWeek Source # 
Instance details

Defined in Data.FuzzyTime.Types

type Rep DayOfWeek = D1 ('MetaData "DayOfWeek" "Data.Time.Calendar.Week" "time-1.9.3" '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))))

Orphan instances

Generic DayOfWeek Source # 
Instance details

Associated Types

type Rep DayOfWeek :: Type -> Type #

NFData DayOfWeek Source # 
Instance details

Methods

rnf :: DayOfWeek -> () #