{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.EN.Corpus
( corpus ) where
import Prelude
import Data.String
import Duckling.Numeral.Types
import Duckling.Testing.Types
corpus :: Corpus
corpus :: Corpus
corpus = (Context
testContext, Options
testOptions, [Example]
allExamples)
allExamples :: [Example]
allExamples :: [Example]
allExamples = [[Example]] -> [Example]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
0)
[ Text
"0"
, Text
"naught"
, Text
"nought"
, Text
"zero"
, Text
"nil"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
1)
[ Text
"1"
, Text
"one"
, Text
"single"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
2)
[ Text
"2"
, Text
"two"
, Text
"a pair"
, Text
"a couple"
, Text
"a couple of"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
3)
[ Text
"3"
, Text
"three"
, Text
"a few"
, Text
"few"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
10)
[ Text
"10"
, Text
"ten"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
12)
[ Text
"12"
, Text
"twelve"
, Text
"a dozen"
, Text
"a dozen of"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
14)
[ Text
"14"
, Text
"fourteen"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
16)
[ Text
"16"
, Text
"sixteen"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
17)
[ Text
"17"
, Text
"seventeen"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
18)
[ Text
"18"
, Text
"eighteen"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
33)
[ Text
"33"
, Text
"thirty three"
, Text
"0033"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
24)
[ Text
"24"
, Text
"2 dozens"
, Text
"two dozen"
, Text
"Two dozen"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
1.1)
[ Text
"1.1"
, Text
"1.10"
, Text
"01.10"
, Text
"1 point 1"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
0.77)
[ Text
".77"
, Text
"0.77"
, Text
"point 77"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
100000)
[ Text
"100,000"
, Text
"100,000.0"
, Text
"100000"
, Text
"100K"
, Text
"100k"
, Text
"one hundred thousand"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
0.2)
[ Text
"1/5"
, Text
"2/10"
, Text
"3/15"
, Text
"20/100"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
3e6)
[ Text
"3M"
, Text
"3000K"
, Text
"3000000"
, Text
"3,000,000"
, Text
"3 million"
, Text
"30 lakh"
, Text
"30 lkh"
, Text
"30 l"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
1.2e6)
[ Text
"1,200,000"
, Text
"1200000"
, Text
"1.2M"
, Text
"1200k"
, Text
".0012G"
, Text
"12 lakhs"
, Text
"12 lkhs"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
5000)
[ Text
"5 thousand"
, Text
"five thousand"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue (-Double
504))
[ Text
"-504"
, Text
"negative five hundred and four"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue (-Double
1.2e6))
[ Text
"- 1,200,000"
, Text
"-1200000"
, Text
"minus 1,200,000"
, Text
"negative 1200000"
, Text
"-1.2M"
, Text
"-1200K"
, Text
"-.0012G"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue (-Double
3200000))
[ Text
"-3,200,000"
, Text
"-3200000"
, Text
"minus three million two hundred thousand"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
122)
[ Text
"one twenty two"
, Text
"ONE TwentY tWO"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
2e5)
[ Text
"two Hundred thousand"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
21011)
[ Text
"twenty-one thousand Eleven"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
721012)
[ Text
"seven hundred twenty-one thousand twelve"
, Text
"seven hundred twenty-one thousand and twelve"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
31256721)
[ Text
"thirty-one million two hundred fifty-six thousand seven hundred twenty-one"
, Text
"three crore twelve lakh fifty-six thousand seven hundred twenty-one"
, Text
"three cr twelve lac fifty-six thousand seven hundred twenty-one"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
2400)
[ Text
"two hundred dozens"
, Text
"200 dozens"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
2200000)
[ Text
"two point two million"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
3000000000)
[ Text
"three billions"
, Text
"three thousand millions"
, Text
"three hundred crores"
, Text
"three hundred Cr"
, Text
"three hundred koti"
, Text
"three hundred krores"
, Text
"three hundred Kr"
]
]