duckling-0.1.1.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 

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

Show (Dimension a) Source # 
Hashable (Dimension a) Source # 

Methods

hashWithSalt :: Int -> Dimension a -> Int

hash :: Dimension a -> Int

TextShow (Dimension a) Source # 

Methods

showbPrec :: Int -> Dimension a -> Builder

showb :: Dimension a -> Builder

showbList :: [Dimension a] -> Builder

showtPrec :: Int -> Dimension a -> Text

showt :: Dimension a -> Text

showtList :: [Dimension a] -> Text

showtlPrec :: Int -> Dimension a -> Text

showtl :: Dimension a -> Text

showtlList :: [Dimension a] -> Text

GShow * Dimension Source # 

Methods

gshowsPrec :: Int -> t a -> ShowS

GEq * Dimension Source # 

Methods

geq :: f a -> f b -> Maybe ((Dimension := a) b)

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

Methods

showbPrec :: Int -> Some * Dimension -> Builder

showb :: Some * Dimension -> Builder

showbList :: [Some * Dimension] -> Builder

showtPrec :: Int -> Some * Dimension -> Text

showt :: Some * Dimension -> Text

showtList :: [Some * Dimension] -> Text

showtlPrec :: Int -> Some * Dimension -> Text

showtl :: Some * Dimension -> Text

showtlList :: [Some * Dimension] -> Text

data Entity Source #

Constructors

Entity 

Fields

Instances

Eq Entity Source # 

Methods

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

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

Show Entity Source # 
Generic Entity Source # 

Associated Types

type Rep Entity :: * -> * #

Methods

from :: Entity -> Rep Entity x #

to :: Rep Entity x -> Entity #

NFData Entity Source # 

Methods

rnf :: Entity -> () #

ToJSON Entity Source # 

Methods

toJSON :: Entity -> Value

toEncoding :: Entity -> Encoding

toJSONList :: [Entity] -> Value

toEncodingList :: [Entity] -> Encoding

type Rep Entity Source # 

data Lang Source #

Constructors

AR 
CS 
DA 
DE 
EN 
ES 
ET 
FR 
GA 
HE 
HR 
ID 
IT 
JA 
KO 
MY 
NB 
NL 
PL 
PT 
RO 
RU 
SV 
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 # 

Methods

showbPrec :: Int -> Lang -> Builder

showb :: Lang -> Builder

showbList :: [Lang] -> Builder

showtPrec :: Int -> Lang -> Text

showt :: Lang -> Text

showtList :: [Lang] -> Text

showtlPrec :: Int -> Lang -> Text

showtl :: Lang -> Text

showtlList :: [Lang] -> Text

type Rep Lang Source # 
type Rep Lang = D1 (MetaData "Lang" "Duckling.Lang" "duckling-0.1.1.0-C08zKxaAjdQ7nnZQDuNARP" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "AR" PrefixI False) U1) ((:+:) (C1 (MetaCons "CS" PrefixI False) U1) (C1 (MetaCons "DA" PrefixI False) U1))) ((:+:) (C1 (MetaCons "DE" 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 "HR" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ID" PrefixI False) U1) (C1 (MetaCons "IT" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "JA" PrefixI False) U1) ((:+:) (C1 (MetaCons "KO" PrefixI False) U1) (C1 (MetaCons "MY" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "NB" 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 "TR" PrefixI False) U1) (C1 (MetaCons "UK" PrefixI False) U1)) ((:+:) (C1 (MetaCons "VI" PrefixI False) U1) (C1 (MetaCons "ZH" PrefixI False) U1))))))

data Some k tag :: 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) 

Methods

showbPrec :: Int -> Some * Dimension -> Builder

showb :: Some * Dimension -> Builder

showbList :: [Some * Dimension] -> Builder

showtPrec :: Int -> Some * Dimension -> Text

showt :: Some * Dimension -> Text

showtList :: [Some * Dimension] -> Text

showtlPrec :: Int -> Some * Dimension -> Text

showtl :: Some * Dimension -> Text

showtlList :: [Some * Dimension] -> Text

toName :: Dimension a -> Text Source #

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