PT: Bring latest changes

Summary: * PhoneNumber: support for "ramal" as extension keyword

Reviewed By: niteria

Differential Revision: D4959209

fbshipit-source-id: cd12c1f
This commit is contained in:
Julien Odent 2017-04-28 07:46:22 -07:00 committed by Facebook Github Bot
parent 5ba2c9e9a1
commit 9269727617
7 changed files with 123 additions and 1 deletions

View File

@ -67,4 +67,10 @@ allExamples = concat
, examples (PhoneNumberValue "61992852776")
[ "61 - 9 9285-2776"
]
, examples (PhoneNumberValue "19997424919")
[ "(19) 997424919"
]
, examples (PhoneNumberValue "(+55) 19992842606")
[ "+55 19992842606"
]
]

View File

@ -0,0 +1,31 @@
-- 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.PhoneNumber.PT.Corpus
( corpus
) where
import Prelude
import Data.String
import Duckling.Lang
import Duckling.PhoneNumber.Types
import Duckling.Resolve
import Duckling.Testing.Types
corpus :: Corpus
corpus = (testContext {lang = PT}, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (PhoneNumberValue "6502834757 ext 897")
[ "(650)-283-4757 ramal 897"
]
]

View File

@ -0,0 +1,56 @@
-- 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 OverloadedStrings #-}
module Duckling.PhoneNumber.PT.Rules
( rules ) where
import Data.String
import Prelude
import qualified Data.Text as Text
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers (parseInt)
import Duckling.PhoneNumber.Types (PhoneNumberData(..))
import Duckling.Regex.Types
import Duckling.Types
import qualified Duckling.PhoneNumber.Types as TPhoneNumber
rulePhoneNumber :: Rule
rulePhoneNumber = Rule
{ name = "phone number"
, pattern =
-- We somewhat arbitrarly use 20 here to limit the length of matches,
-- otherwise due to backtracking the regexp will take very long time
-- or run out of stack for some inputs.
[ regex $
"(?:\\(?\\+(\\d{1,2})\\)?[\\s-\\.]*)?" ++ -- area code
"((?=[-\\d()\\s\\.]{6,16}(?:\\s*ramal\\.?\\s*(?:\\d{1,20}))?(?:[^\\d]+|$))(?:[\\d(]{1,20}(?:[-)\\s\\.]*\\d{1,20}){0,20}){1,20})" ++ -- nums
"(?:\\s*ramal\\.?\\s*(\\d{1,20}))?" -- extension
]
, prod = \xs -> case xs of
(Token RegexMatch (GroupMatch (code:nums:ext:_)):_) ->
let parseNum x = toInteger <$> parseInt x
mcode = parseNum code
mext = parseNum ext
cleanup = Text.filter (not . isWhitespace)
isWhitespace x = elem x ['.', ' ', '-', '\t', '(', ')']
in Just . Token PhoneNumber $ PhoneNumberData
{ TPhoneNumber.prefix = mcode
, TPhoneNumber.number = cleanup nums
, TPhoneNumber.extension = mext
}
_ -> Nothing
}
rules :: [Rule]
rules =
[ rulePhoneNumber
]

View File

@ -18,6 +18,7 @@ import qualified Duckling.AmountOfMoney.PT.Rules as AmountOfMoney
import qualified Duckling.Distance.PT.Rules as Distance
import qualified Duckling.Numeral.PT.Rules as Numeral
import qualified Duckling.Ordinal.PT.Rules as Ordinal
import qualified Duckling.PhoneNumber.PT.Rules as PhoneNumber
import qualified Duckling.Quantity.PT.Rules as Quantity
import qualified Duckling.Temperature.PT.Rules as Temperature
import qualified Duckling.Time.PT.Rules as Time
@ -32,7 +33,7 @@ rules (This Numeral) = Numeral.rules
rules (This Email) = []
rules (This AmountOfMoney) = AmountOfMoney.rules
rules (This Ordinal) = Ordinal.rules
rules (This PhoneNumber) = []
rules (This PhoneNumber) = PhoneNumber.rules
rules (This Quantity) = Quantity.rules
rules (This RegexMatch) = []
rules (This Temperature) = Temperature.rules

View File

@ -331,6 +331,8 @@ library
, Duckling.Ordinal.Types
-- PhoneNumber
, Duckling.PhoneNumber.PT.Corpus
, Duckling.PhoneNumber.PT.Rules
, Duckling.PhoneNumber.Corpus
, Duckling.PhoneNumber.Rules
, Duckling.PhoneNumber.Types
@ -626,6 +628,7 @@ test-suite duckling-test
, Duckling.Ordinal.Tests
-- PhoneNumber
, Duckling.PhoneNumber.PT.Tests
, Duckling.PhoneNumber.Tests
-- Quantity

View File

@ -0,0 +1,23 @@
-- 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.
module Duckling.PhoneNumber.PT.Tests
( tests
) where
import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.PhoneNumber.PT.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "PhoneNumber Tests"
[ makeCorpusTest [This PhoneNumber] corpus
]

View File

@ -22,12 +22,14 @@ import Duckling.PhoneNumber.Corpus
import Duckling.PhoneNumber.Types
import Duckling.Testing.Asserts
import Duckling.Testing.Types
import qualified Duckling.PhoneNumber.PT.Tests as PT
tests :: TestTree
tests = testGroup "PhoneNumber Tests"
[ makeCorpusTest [This PhoneNumber] corpus
, makeNegativeCorpusTest [This PhoneNumber] negativeCorpus
, surroundTests
, PT.tests
]
surroundTests :: TestTree