duckling-0.1.6.1: A Haskell library for parsing text into structured data.

Safe HaskellNone
LanguageHaskell2010

Duckling.Core

Description

Everything needed to run Duckling.

Synopsis

Documentation

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

data Entity Source #

Constructors

Entity 

Fields

data Lang Source #

Constructors

AR 
BG 
CS 
DA 
DE 
EL 
EN 
ES 
ET 
FR 
GA 
HE 
HI 
HR 
HU 
ID 
IT 
JA 
KA 
KO 
MY 
NB 
NE 
NL 
PL 
PT 
RO 
RU 
SV 
TA 
TR 
UK 
VI 
ZH 

Instances

Bounded Lang Source # 
Enum Lang Source # 

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 # 

Methods

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

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

Ord Lang Source # 

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 # 
Show Lang Source # 

Methods

showsPrec :: Int -> Lang -> ShowS #

show :: Lang -> String #

showList :: [Lang] -> ShowS #

Generic Lang Source # 

Associated Types

type Rep Lang :: * -> * #

Methods

from :: Lang -> Rep Lang x #

to :: Rep Lang x -> Lang #

Hashable Lang Source # 

Methods

hashWithSalt :: Int -> Lang -> Int #

hash :: Lang -> Int #

TextShow Lang Source # 
type Rep Lang Source # 
type Rep Lang = D1 * (MetaData "Lang" "Duckling.Locale" "duckling-0.1.6.1-83m0Jl1y16C43giMGsHrS3" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "AR" PrefixI False) (U1 *)) (C1 * (MetaCons "BG" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "CS" PrefixI False) (U1 *)) (C1 * (MetaCons "DA" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "DE" PrefixI False) (U1 *)) (C1 * (MetaCons "EL" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "EN" PrefixI False) (U1 *)) (C1 * (MetaCons "ES" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ET" PrefixI False) (U1 *)) (C1 * (MetaCons "FR" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "GA" PrefixI False) (U1 *)) (C1 * (MetaCons "HE" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "HI" PrefixI False) (U1 *)) (C1 * (MetaCons "HR" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "HU" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ID" PrefixI False) (U1 *)) (C1 * (MetaCons "IT" PrefixI False) (U1 *))))))) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "JA" PrefixI False) (U1 *)) (C1 * (MetaCons "KA" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "KO" PrefixI False) (U1 *)) (C1 * (MetaCons "MY" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "NB" PrefixI False) (U1 *)) (C1 * (MetaCons "NE" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NL" PrefixI False) (U1 *)) (C1 * (MetaCons "PL" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "PT" PrefixI False) (U1 *)) (C1 * (MetaCons "RO" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "RU" PrefixI False) (U1 *)) (C1 * (MetaCons "SV" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "TA" PrefixI False) (U1 *)) (C1 * (MetaCons "TR" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "UK" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "VI" PrefixI False) (U1 *)) (C1 * (MetaCons "ZH" PrefixI False) (U1 *))))))))

data Node Source #

Constructors

Node 

Fields

Instances

Eq Node Source # 

Methods

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

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

Show Node Source # 

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

Generic Node Source # 

Associated Types

type Rep Node :: * -> * #

Methods

from :: Node -> Rep Node x #

to :: Rep Node x -> Node #

NFData Node Source # 

Methods

rnf :: Node -> () #

Hashable Node Source # 

Methods

hashWithSalt :: Int -> Node -> Int #

hash :: Node -> Int #

type Rep Node Source # 

newtype Options Source #

Constructors

Options 

Fields

data Range Source #

Constructors

Range Int Int 

Instances

Eq Range Source # 

Methods

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

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

Ord Range Source # 

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 # 

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

Generic Range Source # 

Associated Types

type Rep Range :: * -> * #

Methods

from :: Range -> Rep Range x #

to :: Rep Range x -> Range #

NFData Range Source # 

Methods

rnf :: Range -> () #

Hashable Range Source # 

Methods

hashWithSalt :: Int -> Range -> Int #

hash :: Range -> Int #

type Rep Range Source # 

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 
CA 
CN 
GB 
HK 
IE 
IN 
JM 
MO 
NZ 
PH 
TT 
TW 
US 
ZA 

Instances

Bounded Region Source # 
Enum Region Source # 
Eq Region Source # 

Methods

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

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

Ord Region Source # 
Read Region Source # 
Show Region Source # 
Generic Region Source # 

Associated Types

type Rep Region :: * -> * #

Methods

from :: Region -> Rep Region x #

to :: Rep Region x -> Region #

Hashable Region Source # 

Methods

hashWithSalt :: Int -> Region -> Int #

hash :: Region -> Int #

TextShow Region Source # 
type Rep Region Source # 
type Rep Region = D1 * (MetaData "Region" "Duckling.Region" "duckling-0.1.6.1-83m0Jl1y16C43giMGsHrS3" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "AU" PrefixI False) (U1 *)) (C1 * (MetaCons "BE" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "BZ" PrefixI False) (U1 *)) (C1 * (MetaCons "CA" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "CN" PrefixI False) (U1 *)) (C1 * (MetaCons "GB" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "HK" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "IE" PrefixI False) (U1 *)) (C1 * (MetaCons "IN" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "JM" PrefixI False) (U1 *)) (C1 * (MetaCons "MO" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NL" PrefixI False) (U1 *)) (C1 * (MetaCons "NZ" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "PH" PrefixI False) (U1 *)) (C1 * (MetaCons "TT" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "TW" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "US" PrefixI False) (U1 *)) (C1 * (MetaCons "ZA" PrefixI False) (U1 *)))))))

data Some k (tag :: k -> *) :: forall k. (k -> *) -> * where #

Constructors

This :: Some k tag 

Instances

GEq k tag => Eq (Some k tag) 

Methods

(==) :: Some k tag -> Some k tag -> Bool #

(/=) :: Some k tag -> Some k tag -> Bool #

GCompare k tag => Ord (Some k tag) 

Methods

compare :: Some k tag -> Some k tag -> Ordering #

(<) :: Some k tag -> Some k tag -> Bool #

(<=) :: Some k tag -> Some k tag -> Bool #

(>) :: Some k tag -> Some k tag -> Bool #

(>=) :: Some k tag -> Some k tag -> Bool #

max :: Some k tag -> Some k tag -> Some k tag #

min :: Some k tag -> Some k tag -> Some k tag #

GRead k f => Read (Some k f) 

Methods

readsPrec :: Int -> ReadS (Some k f) #

readList :: ReadS [Some k f] #

readPrec :: ReadPrec (Some k f) #

readListPrec :: ReadPrec [Some k f] #

GShow k tag => Show (Some k tag) 

Methods

showsPrec :: Int -> Some k tag -> ShowS #

show :: Some k tag -> String #

showList :: [Some k tag] -> ShowS #

Hashable (Some * Dimension) # 
TextShow (Some * Dimension) # 

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

parse :: Text -> Context -> Options -> [Some 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.