duckling/Duckling/Number/Helpers.hs
Jonathan Coens 1b91b70c58 codemod DNumber to Numeral
Summary: `DNumber` is a terrible name and was only there because legacy. `Numeral` makes more sense for this dimension, so let's use that instead.

Reviewed By: patapizza

Differential Revision: D4707167

fbshipit-source-id: cd78aa3
2017-03-14 13:34:11 -07:00

129 lines
3.4 KiB
Haskell

-- 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.Number.Helpers
( decimalsToDouble
, double
, integer
, multiply
, numberBetween
, numberWith
, oneOf
, parseDouble
, parseInt
, withGrain
, withMultipliable
, parseDecimal,
) where
import qualified Data.Attoparsec.Text as Atto
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as Text
import Prelude
import Duckling.Dimensions.Types
import Duckling.Number.Types (NumberData (..))
import qualified Duckling.Number.Types as TNumber
import Duckling.Types
zeroT :: Text
zeroT = Text.singleton '0'
dot :: Text
dot = Text.singleton '.'
comma :: Text
comma = Text.singleton ','
parseInt :: Text -> Maybe Int
parseInt =
either (const Nothing) Just . Atto.parseOnly (Atto.signed Atto.decimal)
-- | Add leading 0 when leading . for double parsing to succeed
parseDouble :: Text -> Maybe Double
parseDouble s
| Text.head s == '.' = go $ Text.append zeroT s
| otherwise = go s
where go = either (const Nothing) Just . Atto.parseOnly Atto.double
-- | 77 -> .77
-- | Find the first power of ten larger that the actual number
-- | Use it to divide x
decimalsToDouble :: Double -> Double
decimalsToDouble x =
let xs = filter (\y -> x - y < 0)
. take 10
. iterate (*10) $ 1 in
case xs of
[] -> 0
(multiplier : _) -> x / multiplier
-- -----------------------------------------------------------------
-- Patterns
numberWith :: (NumberData -> t) -> (t -> Bool) -> PatternItem
numberWith f pred = Predicate $ \x ->
case x of
(Token Numeral x@NumberData{}) -> pred (f x)
_ -> False
numberBetween :: Double -> Double -> PatternItem
numberBetween low up = Predicate $ \x ->
case x of
(Token Numeral NumberData {TNumber.value = v, TNumber.multipliable = False}) ->
low <= v && v < up
_ -> False
oneOf :: [Double] -> PatternItem
oneOf vs = Predicate $ \x ->
case x of
(Token Numeral NumberData {TNumber.value = v}) -> elem v vs
_ -> False
-- -----------------------------------------------------------------
-- Production
withMultipliable :: Token -> Maybe Token
withMultipliable (Token Numeral x@NumberData{}) =
Just . Token Numeral $ x {TNumber.multipliable = True}
withMultipliable _ = Nothing
withGrain :: Int -> Token -> Maybe Token
withGrain g (Token Numeral x@NumberData{}) =
Just . Token Numeral $ x {TNumber.grain = Just g}
withGrain _ _ = Nothing
double :: Double -> Maybe Token
double x = Just . Token Numeral $ NumberData
{ TNumber.value = x
, TNumber.grain = Nothing
, TNumber.multipliable = False
}
integer :: Integer -> Maybe Token
integer = double . fromIntegral
multiply :: Token -> Token -> Maybe Token
multiply
(Token Numeral (NumberData {TNumber.value = v1}))
(Token Numeral (NumberData {TNumber.value = v2, TNumber.grain = g})) = case g of
Nothing -> double $ v1 * v2
Just grain | v2 > v1 -> double (v1 * v2) >>= withGrain grain
| otherwise -> Nothing
multiply _ _ = Nothing
parseDecimal :: Bool -> Text -> Maybe Token
parseDecimal isDot match
| isDot = parseDouble match >>= double
| otherwise =
parseDouble (Text.replace comma dot match)
>>= double