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

Duckling.Core

Description

Everything needed to run Duckling.

Synopsis

Documentation

data Context Source #

Constructors

Context 

Instances

Instances details
Eq Context Source # 
Instance details

Defined in Duckling.Resolve

Methods

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

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

Show Context Source # 
Instance details

Defined in Duckling.Resolve

data Dimension a where Source #

GADT for differentiating between dimensions Each dimension should have its own constructor and provide the data structure for its parsed data

Instances

Instances details
Show (Dimension a) Source # 
Instance details

Defined in Duckling.Types

Hashable (Dimension a) Source # 
Instance details

Defined in Duckling.Types

Methods

hashWithSalt :: Int -> Dimension a -> Int #

hash :: Dimension a -> Int #

Hashable (Seal Dimension) Source # 
Instance details

Defined in Duckling.Types

TextShow (Dimension a) Source # 
Instance details

Defined in Duckling.Types

TextShow (Seal Dimension) Source # 
Instance details

Defined in Duckling.Types

GShow Dimension Source # 
Instance details

Defined in Duckling.Types

Methods

gshowsPrec :: forall (a :: k). Int -> Dimension a -> ShowS #

GEq Dimension Source # 
Instance details

Defined in Duckling.Types

Methods

geq :: forall (a :: k) (b :: k). Dimension a -> Dimension b -> Maybe (a :~: b) #

data Entity Source #

Constructors

Entity 

Fields

Instances

Instances details
Eq Entity Source # 
Instance details

Defined in Duckling.Types

Methods

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

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

Show Entity Source # 
Instance details

Defined in Duckling.Types

Generic Entity Source # 
Instance details

Defined in Duckling.Types

Associated Types

type Rep Entity :: Type -> Type #

Methods

from :: Entity -> Rep Entity x #

to :: Rep Entity x -> Entity #

ToJSON Entity Source # 
Instance details

Defined in Duckling.Types

type Rep Entity Source # 
Instance details

Defined in Duckling.Types

data Lang Source #

Constructors

AF 
AR 
BG 
BN 
CA 
CS 
DA 
DE 
EL 
EN 
ES 
ET 
FA 
FI 
FR 
GA 
HE 
HI 
HR 
HU 
ID 
IS 
IT 
JA 
KA 
KN 
KM 
KO 
LO 
ML 
MN 
MY 
NB 
NE 
NL 
PL 
PT 
RO 
RU 
SK 
SV 
SW 
TA 
TE 
TH 
TR 
UK 
VI 
ZH 

Instances

Instances details
Bounded Lang Source # 
Instance details

Defined in Duckling.Locale

Enum Lang Source # 
Instance details

Defined in Duckling.Locale

Methods

succ :: Lang -> Lang #

pred :: Lang -> Lang #

toEnum :: Int -> Lang #

fromEnum :: Lang -> Int #

enumFrom :: Lang -> [Lang] #

enumFromThen :: Lang -> Lang -> [Lang] #

enumFromTo :: Lang -> Lang -> [Lang] #

enumFromThenTo :: Lang -> Lang -> Lang -> [Lang] #

Eq Lang Source # 
Instance details

Defined in Duckling.Locale

Methods

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

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

Ord Lang Source # 
Instance details

Defined in Duckling.Locale

Methods

compare :: Lang -> Lang -> Ordering #

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

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

(>) :: Lang -> Lang -> Bool #

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

max :: Lang -> Lang -> Lang #

min :: Lang -> Lang -> Lang #

Read Lang Source # 
Instance details

Defined in Duckling.Locale

Show Lang Source # 
Instance details

Defined in Duckling.Locale

Methods

showsPrec :: Int -> Lang -> ShowS #

show :: Lang -> String #

showList :: [Lang] -> ShowS #

Generic Lang Source # 
Instance details

Defined in Duckling.Locale

Associated Types

type Rep Lang :: Type -> Type #

Methods

from :: Lang -> Rep Lang x #

to :: Rep Lang x -> Lang #

Hashable Lang Source # 
Instance details

Defined in Duckling.Locale

Methods

hashWithSalt :: Int -> Lang -> Int #

hash :: Lang -> Int #

TextShow Lang Source # 
Instance details

Defined in Duckling.Locale

type Rep Lang Source # 
Instance details

Defined in Duckling.Locale

type Rep Lang = D1 ('MetaData "Lang" "Duckling.Locale" "duckling-0.2.0.0-4AU1pRwMU7E8YjNdB7ILfy" 'False) (((((C1 ('MetaCons "AF" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BG" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "BN" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CS" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EL" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "EN" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ES" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ET" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "FA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FR" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "GA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HI" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "HR" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HU" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ID" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "IS" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JA" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "KA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KM" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KO" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LO" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ML" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "MN" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NB" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "NE" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PL" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "PT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RO" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RU" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SK" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SV" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SW" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "TA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TH" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UK" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "VI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ZH" 'PrefixI 'False) (U1 :: Type -> Type)))))))

data Locale Source #

Instances

Instances details
Eq Locale Source # 
Instance details

Defined in Duckling.Locale

Methods

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

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

Ord Locale Source # 
Instance details

Defined in Duckling.Locale

Show Locale Source # 
Instance details

Defined in Duckling.Locale

Generic Locale Source # 
Instance details

Defined in Duckling.Locale

Associated Types

type Rep Locale :: Type -> Type #

Methods

from :: Locale -> Rep Locale x #

to :: Rep Locale x -> Locale #

Hashable Locale Source # 
Instance details

Defined in Duckling.Locale

Methods

hashWithSalt :: Int -> Locale -> Int #

hash :: Locale -> Int #

TextShow Locale Source # 
Instance details

Defined in Duckling.Locale

type Rep Locale Source # 
Instance details

Defined in Duckling.Locale

type Rep Locale = D1 ('MetaData "Locale" "Duckling.Locale" "duckling-0.2.0.0-4AU1pRwMU7E8YjNdB7ILfy" 'False) (C1 ('MetaCons "Locale" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lang) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Region))))

data Node Source #

Constructors

Node 

Fields

Instances

Instances details
Eq Node Source # 
Instance details

Defined in Duckling.Types

Methods

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

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

Show Node Source # 
Instance details

Defined in Duckling.Types

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

Generic Node Source # 
Instance details

Defined in Duckling.Types

Associated Types

type Rep Node :: Type -> Type #

Methods

from :: Node -> Rep Node x #

to :: Rep Node x -> Node #

Hashable Node Source # 
Instance details

Defined in Duckling.Types

Methods

hashWithSalt :: Int -> Node -> Int #

hash :: Node -> Int #

NFData Node Source # 
Instance details

Defined in Duckling.Types

Methods

rnf :: Node -> () #

type Rep Node Source # 
Instance details

Defined in Duckling.Types

type Rep Node = D1 ('MetaData "Node" "Duckling.Types" "duckling-0.2.0.0-4AU1pRwMU7E8YjNdB7ILfy" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) ((S1 ('MetaSel ('Just "nodeRange") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range) :*: S1 ('MetaSel ('Just "token") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Token)) :*: (S1 ('MetaSel ('Just "children") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Node]) :*: S1 ('MetaSel ('Just "rule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))

newtype Options Source #

Constructors

Options 

Fields

Instances

Instances details
Eq Options Source # 
Instance details

Defined in Duckling.Resolve

Methods

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

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

Show Options Source # 
Instance details

Defined in Duckling.Resolve

data Range Source #

Constructors

Range Int Int 

Instances

Instances details
Eq Range Source # 
Instance details

Defined in Duckling.Types

Methods

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

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

Ord Range Source # 
Instance details

Defined in Duckling.Types

Methods

compare :: Range -> Range -> Ordering #

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

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

(>) :: Range -> Range -> Bool #

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

max :: Range -> Range -> Range #

min :: Range -> Range -> Range #

Show Range Source # 
Instance details

Defined in Duckling.Types

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

Generic Range Source # 
Instance details

Defined in Duckling.Types

Associated Types

type Rep Range :: Type -> Type #

Methods

from :: Range -> Rep Range x #

to :: Rep Range x -> Range #

Hashable Range Source # 
Instance details

Defined in Duckling.Types

Methods

hashWithSalt :: Int -> Range -> Int #

hash :: Range -> Int #

NFData Range Source # 
Instance details

Defined in Duckling.Types

Methods

rnf :: Range -> () #

type Rep Range Source # 
Instance details

Defined in Duckling.Types

type Rep Range = D1 ('MetaData "Range" "Duckling.Types" "duckling-0.2.0.0-4AU1pRwMU7E8YjNdB7ILfy" 'False) (C1 ('MetaCons "Range" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data Region Source #

ISO 3166-1 alpha-2 Country code (includes regions and territories). See https://en.wikipedia.org/wiki/ISO_3166-1_alpha-2

Constructors

AU 
BE 
BZ 
CL 
CN 
CO 
EG 
GB 
HK 
IE 
IN 
JM 
MX 
MO 
NZ 
PE 
PH 
TT 
TW 
US 
VE 
ZA 

Instances

Instances details
Bounded Region Source # 
Instance details

Defined in Duckling.Region

Enum Region Source # 
Instance details

Defined in Duckling.Region

Eq Region Source # 
Instance details

Defined in Duckling.Region

Methods

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

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

Ord Region Source # 
Instance details

Defined in Duckling.Region

Read Region Source # 
Instance details

Defined in Duckling.Region

Show Region Source # 
Instance details

Defined in Duckling.Region

Generic Region Source # 
Instance details

Defined in Duckling.Region

Associated Types

type Rep Region :: Type -> Type #

Methods

from :: Region -> Rep Region x #

to :: Rep Region x -> Region #

Hashable Region Source # 
Instance details

Defined in Duckling.Region

Methods

hashWithSalt :: Int -> Region -> Int #

hash :: Region -> Int #

TextShow Region Source # 
Instance details

Defined in Duckling.Region

type Rep Region Source # 
Instance details

Defined in Duckling.Region

type Rep Region = D1 ('MetaData "Region" "Duckling.Region" "duckling-0.2.0.0-4AU1pRwMU7E8YjNdB7ILfy" 'False) ((((C1 ('MetaCons "AR" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AU" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BE" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "BZ" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CL" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CN" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CO" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EG" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ES" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GB" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HK" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IE" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "IN" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "JM" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MN" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MO" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NZ" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PE" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PH" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TW" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "US" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "VE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ZA" 'PrefixI 'False) (U1 :: Type -> Type))))))

data ResolvedVal Source #

Constructors

forall a.(Resolve a, Eq (ResolvedValue a), Show (ResolvedValue a), ToJSON (ResolvedValue a)) => RVal (Dimension a) (ResolvedValue a) 

Instances

Instances details
Eq ResolvedVal Source # 
Instance details

Defined in Duckling.Types

Show ResolvedVal Source # 
Instance details

Defined in Duckling.Types

data Seal s where Source #

Constructors

Seal :: s a -> Seal s 

Instances

Instances details
GEq s => Eq (Seal s) Source # 
Instance details

Defined in Duckling.Types

Methods

(==) :: Seal s -> Seal s -> Bool #

(/=) :: Seal s -> Seal s -> Bool #

GShow s => Show (Seal s) Source # 
Instance details

Defined in Duckling.Types

Methods

showsPrec :: Int -> Seal s -> ShowS #

show :: Seal s -> String #

showList :: [Seal s] -> ShowS #

Hashable (Seal Dimension) Source # 
Instance details

Defined in Duckling.Types

TextShow (Seal Dimension) Source # 
Instance details

Defined in Duckling.Types

withSeal :: Seal s -> (forall t. s t -> r) -> r Source #

toJText :: ToJSON x => x -> Text Source #

parse :: Text -> Context -> Options -> [Seal Dimension] -> [Entity] Source #

Parses input and returns a curated list of entities found.

currentReftime :: HashMap Text TimeZoneSeries -> Text -> IO DucklingTime Source #

Builds a DucklingTime for timezone tz at current time. If no series found for tz, uses UTC.

makeReftime :: HashMap Text TimeZoneSeries -> Text -> UTCTime -> DucklingTime Source #

Builds a DucklingTime for timezone tz at utcTime. If no series found for tz, uses UTC.