fuzzy-time-0.2.0.3
Safe HaskellSafe-Inferred
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

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 #

Show Month Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

showsPrec :: Int -> Month -> ShowS #

show :: Month -> String #

showList :: [Month] -> ShowS #

NFData Month Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: Month -> () #

Eq Month Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

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

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

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.3-BCtVpf4xo0m8oKp4WU6Smy" '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
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 #

Show FuzzyDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

NFData FuzzyDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: FuzzyDay -> () #

Eq FuzzyDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

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.3-BCtVpf4xo0m8oKp4WU6Smy" '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
Generic FuzzyTimeOfDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

Associated Types

type Rep FuzzyTimeOfDay :: Type -> Type #

Show FuzzyTimeOfDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

NFData FuzzyTimeOfDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: FuzzyTimeOfDay -> () #

Eq FuzzyTimeOfDay Source # 
Instance details

Defined in Data.FuzzyTime.Types

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.3-BCtVpf4xo0m8oKp4WU6Smy" '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
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 #

(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 #

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

Defined in Data.FuzzyTime.Types

Methods

rnf :: Some a b -> () #

(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 #

(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
Generic FuzzyLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Associated Types

type Rep FuzzyLocalTime :: Type -> Type #

Show FuzzyLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

NFData FuzzyLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: FuzzyLocalTime -> () #

Eq FuzzyLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

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

data AmbiguousLocalTime Source #

Instances

Instances details
Generic AmbiguousLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Associated Types

type Rep AmbiguousLocalTime :: Type -> Type #

Show AmbiguousLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

NFData AmbiguousLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: AmbiguousLocalTime -> () #

Eq AmbiguousLocalTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

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.3-BCtVpf4xo0m8oKp4WU6Smy" '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
Generic FuzzyZonedTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Associated Types

type Rep FuzzyZonedTime :: Type -> Type #

Show FuzzyZonedTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

NFData FuzzyZonedTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

Methods

rnf :: FuzzyZonedTime -> () #

Eq FuzzyZonedTime Source # 
Instance details

Defined in Data.FuzzyTime.Types

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.3-BCtVpf4xo0m8oKp4WU6Smy" 'False) (C1 ('MetaCons "ZonedNow" 'PrefixI 'False) (U1 :: Type -> Type))

data DayOfWeek #

Instances

Instances details
Data DayOfWeek 
Instance details

Defined in Data.Time.Calendar.Week

Methods

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

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

toConstr :: DayOfWeek -> Constr #

dataTypeOf :: DayOfWeek -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Generic DayOfWeek Source # 
Instance details

Defined in Data.FuzzyTime.Types

Associated Types

type Rep DayOfWeek :: Type -> Type #

Ix 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

NFData DayOfWeek 
Instance details

Defined in Data.Time.Calendar.Week

Methods

rnf :: DayOfWeek -> () #

Eq DayOfWeek 
Instance details

Defined in Data.Time.Calendar.Week

Ord DayOfWeek 
Instance details

Defined in Data.Time.Calendar.Week

type Rep DayOfWeek Source # 
Instance details

Defined in Data.FuzzyTime.Types

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