Skip to content

Commit

Permalink
Chinese locales + fix TW National Day
Browse files Browse the repository at this point in the history
Summary:
* Moving `ruleNationalDay` from `ZH` rules to specific locales: `zh_CN`, `zh_HK`, `zh_MO`
* Fixed National Day for `zh_TW`.

Reviewed By: blandinw

Differential Revision: D6057565

fbshipit-source-id: 8f9f2ab
  • Loading branch information
patapizza authored and facebook-github-bot committed Oct 14, 2017
1 parent 33a08bb commit fb1dcaa
Show file tree
Hide file tree
Showing 23 changed files with 3,894 additions and 61 deletions.
6 changes: 4 additions & 2 deletions Duckling/Duration/ZH/Corpus.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,15 +12,17 @@ module Duckling.Duration.ZH.Corpus
( corpus
) where

import Prelude
import Data.String
import Prelude

import Duckling.Duration.Types
import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types
import Duckling.TimeGrain.Types (Grain(..))

corpus :: Corpus
corpus = (testContext, allExamples)
corpus = (testContext {locale = makeLocale ZH Nothing}, allExamples)

allExamples :: [Example]
allExamples = concat
Expand Down
7 changes: 6 additions & 1 deletion Duckling/Locale.hs
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,11 @@ instance TextShow Lang where
-- | ISO 3166-1 alpha-2 Country code (includes regions and territories).
-- See https://en.wikipedia.org/wiki/ISO_3166-1_alpha-2
data Region
= GB
= CN
| GB
| HK
| MO
| TW
| US
deriving (Bounded, Enum, Eq, Generic, Hashable, Ord, Read, Show)

Expand Down Expand Up @@ -97,4 +101,5 @@ makeLocale lang (Just region)
allLocales :: HashMap Lang (HashSet Region)
allLocales = HashMap.fromList
[ (EN, HashSet.fromList [GB, US])
, (ZH, HashSet.fromList [CN, HK, MO, TW])
]
879 changes: 879 additions & 0 deletions Duckling/Ranking/Classifiers/ZH_CN.hs

Large diffs are not rendered by default.

879 changes: 879 additions & 0 deletions Duckling/Ranking/Classifiers/ZH_HK.hs

Large diffs are not rendered by default.

879 changes: 879 additions & 0 deletions Duckling/Ranking/Classifiers/ZH_MO.hs

Large diffs are not rendered by default.

879 changes: 879 additions & 0 deletions Duckling/Ranking/Classifiers/ZH_TW.hs

Large diffs are not rendered by default.

29 changes: 7 additions & 22 deletions Duckling/Ranking/Classifiers/ZH_XX.hs
Original file line number Diff line number Diff line change
Expand Up @@ -117,13 +117,6 @@ classifiers
[("<integer> (latent time-of-day)", -0.6931471805599453),
("hour", -0.6931471805599453)],
n = 5}}),
("national day",
Classifier{okData =
ClassData{prior = 0.0, unseen = -2.0794415416798357,
likelihoods = HashMap.fromList [("", 0.0)], n = 6},
koData =
ClassData{prior = -infinity, unseen = -0.6931471805599453,
likelihoods = HashMap.fromList [], n = 0}}),
("Wednesday",
Classifier{okData =
ClassData{prior = 0.0, unseen = -2.9444389791664407,
Expand Down Expand Up @@ -264,13 +257,6 @@ classifiers
koData =
ClassData{prior = -infinity, unseen = -0.6931471805599453,
likelihoods = HashMap.fromList [], n = 0}}),
("evening|night",
Classifier{okData =
ClassData{prior = 0.0, unseen = -1.3862943611198906,
likelihoods = HashMap.fromList [("", 0.0)], n = 2},
koData =
ClassData{prior = -infinity, unseen = -0.6931471805599453,
likelihoods = HashMap.fromList [], n = 0}}),
("Monday",
Classifier{okData =
ClassData{prior = 0.0, unseen = -3.258096538021482,
Expand Down Expand Up @@ -478,17 +464,16 @@ classifiers
likelihoods = HashMap.fromList [], n = 0}}),
("<dim time> <part-of-day>",
Classifier{okData =
ClassData{prior = 0.0, unseen = -3.9889840465642745,
ClassData{prior = 0.0, unseen = -3.891820298110627,
likelihoods =
HashMap.fromList
[("dayhour", -0.7514160886839211),
("national dayevening|night", -2.871679624884012),
("<named-month> <day-of-month>morning", -1.405342556090585),
("children's dayafternoon", -2.871679624884012),
("Mondaymorning", -1.7730673362159024)],
n = 24},
[("dayhour", -0.7357067949787413),
("<named-month> <day-of-month>morning", -1.3062516534463542),
("children's dayafternoon", -2.772588722239781),
("Mondaymorning", -1.6739764335716716)],
n = 22},
koData =
ClassData{prior = -infinity, unseen = -1.791759469228055,
ClassData{prior = -infinity, unseen = -1.6094379124341003,
likelihoods = HashMap.fromList [], n = 0}}),
("<part-of-day> <dim time>",
Classifier{okData =
Expand Down
2 changes: 1 addition & 1 deletion Duckling/Rules/EN.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ defaultRules dim = langRules dim
localeRules :: Region -> Some Dimension -> [Rule]
localeRules GB (This Time) = TimeGB.rules
localeRules US (This Time) = TimeUS.rules
localeRules _ _ = []
localeRules _ _ = []

langRules :: Some Dimension -> [Rule]
langRules (This AmountOfMoney) = AmountOfMoney.rules
Expand Down
10 changes: 9 additions & 1 deletion Duckling/Rules/ZH.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,13 +22,21 @@ import qualified Duckling.Numeral.ZH.Rules as Numeral
import qualified Duckling.Ordinal.ZH.Rules as Ordinal
import qualified Duckling.Temperature.ZH.Rules as Temperature
import qualified Duckling.Time.ZH.Rules as Time
import qualified Duckling.Time.ZH.CN.Rules as TimeCN
import qualified Duckling.Time.ZH.HK.Rules as TimeHK
import qualified Duckling.Time.ZH.MO.Rules as TimeMO
import qualified Duckling.Time.ZH.TW.Rules as TimeTW
import qualified Duckling.TimeGrain.ZH.Rules as TimeGrain

defaultRules :: Some Dimension -> [Rule]
defaultRules = langRules

localeRules :: Region -> Some Dimension -> [Rule]
localeRules _ _ = []
localeRules CN (This Time) = TimeCN.rules
localeRules HK (This Time) = TimeHK.rules
localeRules MO (This Time) = TimeMO.rules
localeRules TW (This Time) = TimeTW.rules
localeRules _ _ = []

langRules :: Some Dimension -> [Rule]
langRules (This AmountOfMoney) = []
Expand Down
37 changes: 37 additions & 0 deletions Duckling/Time/ZH/CN/Corpus.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,37 @@
-- Copyright (c) 2016-present, Facebook, Inc.
-- All rights reserved.
--
-- This source code is licensed under the BSD-style license found in the
-- LICENSE file in the root directory of this source tree. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.


{-# LANGUAGE OverloadedStrings #-}

module Duckling.Time.ZH.CN.Corpus
( allExamples
) where

import Data.String
import Prelude

import Duckling.Testing.Types hiding (examples)
import Duckling.Time.Corpus
import Duckling.Time.Types hiding (Month)
import Duckling.TimeGrain.Types hiding (add)

allExamples :: [Example]
allExamples = concat
[ examples (datetime (2013, 10, 1, 0, 0, 0) Day)
[ "国庆"
, "國慶"
, "国庆节"
, "国庆節"
, "國慶节"
, "國慶節"
]
, examples (datetimeInterval ((2013, 10, 1, 18, 0, 0), (2013, 10, 2, 0, 0, 0)) Hour)
[ "国庆节晚上"
, "國慶節晚上"
]
]
35 changes: 35 additions & 0 deletions Duckling/Time/ZH/CN/Rules.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
-- Copyright (c) 2016-present, Facebook, Inc.
-- All rights reserved.
--
-- This source code is licensed under the BSD-style license found in the
-- LICENSE file in the root directory of this source tree. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.


{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoRebindableSyntax #-}
{-# LANGUAGE OverloadedStrings #-}

module Duckling.Time.ZH.CN.Rules
( rules
) where

import Prelude

import Duckling.Regex.Types
import Duckling.Time.Helpers
import Duckling.Types

ruleNationalDay :: Rule
ruleNationalDay = Rule
{ name = "national day"
, pattern =
[ regex "(国庆|國慶)(节|節)?"
]
, prod = \_ -> tt $ monthDay 10 1
}

rules :: [Rule]
rules =
[ ruleNationalDay
]
19 changes: 7 additions & 12 deletions Duckling/Time/ZH/Corpus.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,17 +9,22 @@
{-# LANGUAGE OverloadedStrings #-}

module Duckling.Time.ZH.Corpus
( corpus ) where
( corpus
, defaultCorpus
) where

import Prelude
import Data.String
import Prelude

import Duckling.Locale
import Duckling.Resolve
import Duckling.Time.Corpus
import Duckling.TimeGrain.Types hiding (add)
import Duckling.Testing.Types hiding (examples)

defaultCorpus :: Corpus
defaultCorpus = corpus

corpus :: Corpus
corpus = (testContext {locale = makeLocale ZH Nothing}, allExamples)

Expand Down Expand Up @@ -482,22 +487,12 @@ allExamples = concat
[ "建军节"
, "建軍節"
]
, examples (datetime (2013, 10, 1, 0, 0, 0) Day)
[ "国庆"
, "國慶"
, "国庆节"
, "國慶節"
]
, examples (datetime (2013, 12, 25, 0, 0, 0) Day)
[ "圣诞"
, "聖誕"
, "圣诞节"
, "聖誕節"
]
, examples (datetimeInterval ((2013, 10, 1, 18, 0, 0), (2013, 10, 2, 0, 0, 0)) Hour)
[ "国庆节晚上"
, "國慶節晚上"
]
, examples (datetime (2013, 6, 1, 15, 15, 0) Minute)
[ "儿童节下午三点十五"
, "兒童節下午三點十五"
Expand Down
37 changes: 37 additions & 0 deletions Duckling/Time/ZH/HK/Corpus.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,37 @@
-- Copyright (c) 2016-present, Facebook, Inc.
-- All rights reserved.
--
-- This source code is licensed under the BSD-style license found in the
-- LICENSE file in the root directory of this source tree. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.


{-# LANGUAGE OverloadedStrings #-}

module Duckling.Time.ZH.HK.Corpus
( allExamples
) where

import Data.String
import Prelude

import Duckling.Testing.Types hiding (examples)
import Duckling.Time.Corpus
import Duckling.Time.Types hiding (Month)
import Duckling.TimeGrain.Types hiding (add)

allExamples :: [Example]
allExamples = concat
[ examples (datetime (2013, 10, 1, 0, 0, 0) Day)
[ "国庆"
, "國慶"
, "国庆节"
, "国庆節"
, "國慶节"
, "國慶節"
]
, examples (datetimeInterval ((2013, 10, 1, 18, 0, 0), (2013, 10, 2, 0, 0, 0)) Hour)
[ "国庆节晚上"
, "國慶節晚上"
]
]
35 changes: 35 additions & 0 deletions Duckling/Time/ZH/HK/Rules.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
-- Copyright (c) 2016-present, Facebook, Inc.
-- All rights reserved.
--
-- This source code is licensed under the BSD-style license found in the
-- LICENSE file in the root directory of this source tree. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.


{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoRebindableSyntax #-}
{-# LANGUAGE OverloadedStrings #-}

module Duckling.Time.ZH.HK.Rules
( rules
) where

import Prelude

import Duckling.Regex.Types
import Duckling.Time.Helpers
import Duckling.Types

ruleNationalDay :: Rule
ruleNationalDay = Rule
{ name = "national day"
, pattern =
[ regex "(国庆|國慶)(节|節)?"
]
, prod = \_ -> tt $ monthDay 10 1
}

rules :: [Rule]
rules =
[ ruleNationalDay
]
37 changes: 37 additions & 0 deletions Duckling/Time/ZH/MO/Corpus.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,37 @@
-- Copyright (c) 2016-present, Facebook, Inc.
-- All rights reserved.
--
-- This source code is licensed under the BSD-style license found in the
-- LICENSE file in the root directory of this source tree. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.


{-# LANGUAGE OverloadedStrings #-}

module Duckling.Time.ZH.MO.Corpus
( allExamples
) where

import Data.String
import Prelude

import Duckling.Testing.Types hiding (examples)
import Duckling.Time.Corpus
import Duckling.Time.Types hiding (Month)
import Duckling.TimeGrain.Types hiding (add)

allExamples :: [Example]
allExamples = concat
[ examples (datetime (2013, 10, 1, 0, 0, 0) Day)
[ "国庆"
, "國慶"
, "国庆节"
, "国庆節"
, "國慶节"
, "國慶節"
]
, examples (datetimeInterval ((2013, 10, 1, 18, 0, 0), (2013, 10, 2, 0, 0, 0)) Hour)
[ "国庆节晚上"
, "國慶節晚上"
]
]
35 changes: 35 additions & 0 deletions Duckling/Time/ZH/MO/Rules.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
-- Copyright (c) 2016-present, Facebook, Inc.
-- All rights reserved.
--
-- This source code is licensed under the BSD-style license found in the
-- LICENSE file in the root directory of this source tree. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.


{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoRebindableSyntax #-}
{-# LANGUAGE OverloadedStrings #-}

module Duckling.Time.ZH.MO.Rules
( rules
) where

import Prelude

import Duckling.Regex.Types
import Duckling.Time.Helpers
import Duckling.Types

ruleNationalDay :: Rule
ruleNationalDay = Rule
{ name = "national day"
, pattern =
[ regex "(国庆|國慶)(节|節)?"
]
, prod = \_ -> tt $ monthDay 10 1
}

rules :: [Rule]
rules =
[ ruleNationalDay
]
Loading

0 comments on commit fb1dcaa

Please sign in to comment.