duckling-0.2.0.0: A Haskell library for parsing text into structured data.
Safe HaskellNone
LanguageHaskell2010

Duckling.Time.Types

Synopsis

Documentation

data TimeObject Source #

Constructors

TimeObject 

Fields

Instances

Instances details
Eq TimeObject Source # 
Instance details

Defined in Duckling.Time.Types

Show TimeObject Source # 
Instance details

Defined in Duckling.Time.Types

data Form Source #

Constructors

DayOfWeek 
TimeOfDay 

Fields

Month 

Fields

PartOfDay 

Instances

Instances details
Eq Form Source # 
Instance details

Defined in Duckling.Time.Types

Methods

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

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

Ord Form Source # 
Instance details

Defined in Duckling.Time.Types

Methods

compare :: Form -> Form -> Ordering #

(<) :: Form -> Form -> Bool #

(<=) :: Form -> Form -> Bool #

(>) :: Form -> Form -> Bool #

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

max :: Form -> Form -> Form #

min :: Form -> Form -> Form #

Show Form Source # 
Instance details

Defined in Duckling.Time.Types

Methods

showsPrec :: Int -> Form -> ShowS #

show :: Form -> String #

showList :: [Form] -> ShowS #

Generic Form Source # 
Instance details

Defined in Duckling.Time.Types

Associated Types

type Rep Form :: Type -> Type #

Methods

from :: Form -> Rep Form x #

to :: Rep Form x -> Form #

Hashable Form Source # 
Instance details

Defined in Duckling.Time.Types

Methods

hashWithSalt :: Int -> Form -> Int #

hash :: Form -> Int #

NFData Form Source # 
Instance details

Defined in Duckling.Time.Types

Methods

rnf :: Form -> () #

type Rep Form Source # 
Instance details

Defined in Duckling.Time.Types

type Rep Form = D1 ('MetaData "Form" "Duckling.Time.Types" "duckling-0.2.0.0-4AU1pRwMU7E8YjNdB7ILfy" 'False) ((C1 ('MetaCons "DayOfWeek" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TimeOfDay" 'PrefixI 'True) (S1 ('MetaSel ('Just "hours") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "is12H") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :+: (C1 ('MetaCons "Month" 'PrefixI 'True) (S1 ('MetaSel ('Just "month") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "PartOfDay" 'PrefixI 'False) (U1 :: Type -> Type)))

data IntervalDirection Source #

Constructors

Before 
After 

Instances

Instances details
Eq IntervalDirection Source # 
Instance details

Defined in Duckling.Time.Types

Ord IntervalDirection Source # 
Instance details

Defined in Duckling.Time.Types

Show IntervalDirection Source # 
Instance details

Defined in Duckling.Time.Types

Generic IntervalDirection Source # 
Instance details

Defined in Duckling.Time.Types

Associated Types

type Rep IntervalDirection :: Type -> Type #

Hashable IntervalDirection Source # 
Instance details

Defined in Duckling.Time.Types

NFData IntervalDirection Source # 
Instance details

Defined in Duckling.Time.Types

Methods

rnf :: IntervalDirection -> () #

type Rep IntervalDirection Source # 
Instance details

Defined in Duckling.Time.Types

type Rep IntervalDirection = D1 ('MetaData "IntervalDirection" "Duckling.Time.Types" "duckling-0.2.0.0-4AU1pRwMU7E8YjNdB7ILfy" 'False) (C1 ('MetaCons "Before" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "After" 'PrefixI 'False) (U1 :: Type -> Type))

data TimeData Source #

Instances

Instances details
Eq TimeData Source # 
Instance details

Defined in Duckling.Time.Types

Ord TimeData Source # 
Instance details

Defined in Duckling.Time.Types

Show TimeData Source # 
Instance details

Defined in Duckling.Time.Types

Hashable TimeData Source # 
Instance details

Defined in Duckling.Time.Types

Methods

hashWithSalt :: Int -> TimeData -> Int #

hash :: TimeData -> Int #

NFData TimeData Source # 
Instance details

Defined in Duckling.Time.Types

Methods

rnf :: TimeData -> () #

Resolve TimeData Source # 
Instance details

Defined in Duckling.Time.Types

Associated Types

type ResolvedValue TimeData Source #

type ResolvedValue TimeData Source # 
Instance details

Defined in Duckling.Time.Types

data TimeValue Source #

Instances

Instances details
Eq TimeValue Source # 
Instance details

Defined in Duckling.Time.Types

Show TimeValue Source # 
Instance details

Defined in Duckling.Time.Types

ToJSON TimeValue Source # 
Instance details

Defined in Duckling.Time.Types

type SeriesPredicate = TimeObject -> TimeContext -> ([TimeObject], [TimeObject]) Source #

Return a tuple of (past, future) elements

data AMPM Source #

Constructors

AM 
PM 

Instances

Instances details
Eq AMPM Source # 
Instance details

Defined in Duckling.Time.Types

Methods

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

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

Show AMPM Source # 
Instance details

Defined in Duckling.Time.Types

Methods

showsPrec :: Int -> AMPM -> ShowS #

show :: AMPM -> String #

showList :: [AMPM] -> ShowS #

data Season Source #

Regular seasons of the Northern Hemisphere.

Constructors

Season 

Instances

Instances details
Eq Season Source # 
Instance details

Defined in Duckling.Time.Types

Methods

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

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

Ord Season Source # 
Instance details

Defined in Duckling.Time.Types

Show Season Source # 
Instance details

Defined in Duckling.Time.Types

newtype NoShow a Source #

Constructors

NoShow a 

Instances

Instances details
Show (NoShow a) Source # 
Instance details

Defined in Duckling.Time.Types

Methods

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

show :: NoShow a -> String #

showList :: [NoShow a] -> ShowS #

timeSeqMap :: Bool -> (TimeObject -> TimeContext -> Maybe TimeObject) -> Predicate -> SeriesPredicate Source #

Applies f to each interval yielded by g. | Intervals including "now" are in the future.

pad :: Int -> Int -> Text Source #

Zero-pad x to reach length n.

timezoneOffset :: TimeZone -> Text Source #

Return the timezone offset portion of the RFC3339 format, e.g. "-02:00".

toRFC3339 :: ZonedTime -> Text Source #

Return a RFC3339 formatted time, e.g. "2013-02-12T04:30:00.000-02:00". | Backward-compatible with Duckling: fraction of second is milli and padded.

timePlusEnd :: TimeObject -> Grain -> Integer -> TimeObject Source #

Shifts the whole interval by n units of theGrain Returned interval has the same length as the input one

data TimeIntervalType Source #

Closed if the interval between A and B should include B Open if the interval should end right before B

Constructors

Open 
Closed 

timeIntersect :: TimeObject -> TimeObject -> Maybe TimeObject Source #

Intersection between two TimeObject. The resulting grain and end fields are the smallest. Prefers intervals when the range is equal.