Safe Haskell | None |
---|---|
Language | Haskell2010 |
Everything needed to run Duckling.
Synopsis
- data Context = Context {}
- data Dimension a where
- RegexMatch :: Dimension GroupMatch
- AmountOfMoney :: Dimension AmountOfMoneyData
- CreditCardNumber :: Dimension CreditCardNumberData
- Distance :: Dimension DistanceData
- Duration :: Dimension DurationData
- Email :: Dimension EmailData
- Numeral :: Dimension NumeralData
- Ordinal :: Dimension OrdinalData
- PhoneNumber :: Dimension PhoneNumberData
- Quantity :: Dimension QuantityData
- Temperature :: Dimension TemperatureData
- Time :: Dimension TimeData
- TimeGrain :: Dimension Grain
- Url :: Dimension UrlData
- Volume :: Dimension VolumeData
- CustomDimension :: CustomDimension a => a -> Dimension (DimensionData a)
- data Entity = Entity {}
- data Lang
- data Locale
- data Node = Node {}
- newtype Options = Options {
- withLatent :: Bool
- data Range = Range Int Int
- data Region
- data ResolvedVal = forall a.(Resolve a, Eq (ResolvedValue a), Show (ResolvedValue a), ToJSON (ResolvedValue a)) => RVal (Dimension a) (ResolvedValue a)
- data Seal s where
- withSeal :: Seal s -> (forall t. s t -> r) -> r
- fromName :: Text -> Maybe (Seal Dimension)
- makeLocale :: Lang -> Maybe Region -> Locale
- toJText :: ToJSON x => x -> Text
- toName :: Dimension a -> Text
- parse :: Text -> Context -> Options -> [Seal Dimension] -> [Entity]
- supportedDimensions :: HashMap Lang [Seal Dimension]
- allLocales :: HashMap Lang (HashSet Region)
- currentReftime :: HashMap Text TimeZoneSeries -> Text -> IO DucklingTime
- fromZonedTime :: ZonedTime -> DucklingTime
- makeReftime :: HashMap Text TimeZoneSeries -> Text -> UTCTime -> DucklingTime
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
Instances
Instances
ISO 639-1 Language. See https://en.wikipedia.org/wiki/List_of_ISO_639-1_codes
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
Eq Locale Source # | |
Ord Locale Source # | |
Show Locale Source # | |
Generic Locale Source # | |
Hashable Locale Source # | |
Defined in Duckling.Locale | |
TextShow Locale Source # | |
Defined in Duckling.Locale | |
type Rep Locale Source # | |
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)))) |
Instances
Eq Node Source # | |
Show Node Source # | |
Generic Node Source # | |
Hashable Node Source # | |
Defined in Duckling.Types | |
NFData Node Source # | |
Defined in Duckling.Types | |
type Rep Node Source # | |
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))))) |
Instances
Eq Range Source # | |
Ord Range Source # | |
Show Range Source # | |
Generic Range Source # | |
Hashable Range Source # | |
Defined in Duckling.Types | |
NFData Range Source # | |
Defined in Duckling.Types | |
type Rep Range Source # | |
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))) |
ISO 3166-1 alpha-2 Country code (includes regions and territories). See https://en.wikipedia.org/wiki/ISO_3166-1_alpha-2
Instances
data ResolvedVal Source #
forall a.(Resolve a, Eq (ResolvedValue a), Show (ResolvedValue a), ToJSON (ResolvedValue a)) => RVal (Dimension a) (ResolvedValue a) |
Instances
Eq ResolvedVal Source # | |
Defined in Duckling.Types (==) :: ResolvedVal -> ResolvedVal -> Bool # (/=) :: ResolvedVal -> ResolvedVal -> Bool # | |
Show ResolvedVal Source # | |
Defined in Duckling.Types showsPrec :: Int -> ResolvedVal -> ShowS # show :: ResolvedVal -> String # showList :: [ResolvedVal] -> ShowS # |
Instances
GEq s => Eq (Seal s) Source # | |
GShow s => Show (Seal s) Source # | |
Hashable (Seal Dimension) Source # | |
TextShow (Seal Dimension) Source # | |
Defined in Duckling.Types showbPrec :: Int -> Seal Dimension -> Builder # showb :: Seal Dimension -> Builder # showbList :: [Seal Dimension] -> Builder # showtPrec :: Int -> Seal Dimension -> Text # showt :: Seal Dimension -> Text # showtList :: [Seal Dimension] -> Text # showtlPrec :: Int -> Seal Dimension -> Text # showtl :: Seal Dimension -> Text # showtlList :: [Seal Dimension] -> Text # |
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.
fromZonedTime :: ZonedTime -> DucklingTime Source #
Builds a DucklingTime
from a ZonedTime
.
makeReftime :: HashMap Text TimeZoneSeries -> Text -> UTCTime -> DucklingTime Source #
Builds a DucklingTime
for timezone tz
at utcTime
.
If no series
found for tz
, uses UTC.