{-# LANGUAGE OverloadedStrings #-}
module Duckling.Volume.EN.Corpus
( corpus ) where
import Data.String
import Prelude
import Duckling.Testing.Types
import Duckling.Volume.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
[ VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Litre Double
1)
[ Text
"1 liter"
, Text
"1 litre"
, Text
"one liter"
, Text
"a liter"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Litre Double
2)
[ Text
"2 liters"
, Text
"2l"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Litre Double
1000)
[ Text
"1000 liters"
, Text
"thousand liters"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Litre Double
0.5)
[ Text
"half liter"
, Text
"half-litre"
, Text
"half a liter"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Litre Double
0.25)
[ Text
"quarter-litre"
, Text
"fourth of liter"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Millilitre Double
1)
[ Text
"one milliliter"
, Text
"an ml"
, Text
"a millilitre"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Millilitre Double
250)
[ Text
"250 milliliters"
, Text
"250 millilitres"
, Text
"250ml"
, Text
"250mls"
, Text
"250 ml"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Gallon Double
3)
[ Text
"3 gallons"
, Text
"3 gal"
, Text
"3gal"
, Text
"around three gallons"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Gallon Double
0.5)
[ Text
"0.5 gals"
, Text
"1/2 gallon"
, Text
"half a gallon"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Gallon Double
0.1)
[ Text
"0.1 gallons"
, Text
"tenth of a gallon"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Hectolitre Double
3)
[ Text
"3 hectoliters"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> (Double, Double) -> VolumeValue
between Unit
Litre (Double
100,Double
1000))
[ Text
"between 100 and 1000 liters"
, Text
"100-1000 liters"
, Text
"from 100 to 1000 l"
, Text
"100 - 1000 l"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> (Double, Double) -> VolumeValue
between Unit
Litre (Double
2,Double
7))
[ Text
"around 2 -7 l"
, Text
"~2-7 liters"
, Text
"from 2 to 7 l"
, Text
"between 2.0 l and about 7.0 l"
, Text
"between 2l and about 7l"
, Text
"2 - ~7 litres"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
under Unit
Gallon Double
6)
[ Text
"less than six gallons"
, Text
"under six gallon"
, Text
"no more than 6 gals"
, Text
"below 6.0gal"
, Text
"at most six gallons"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
above Unit
Hectolitre Double
2)
[ Text
"exceeding 2 hectoliters"
, Text
"at least two hectolitres"
, Text
"over 2 hectolitre"
, Text
"more than 2 hectoliter"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
above Unit
Millilitre Double
4)
[ Text
"exceeding 4 ml"
, Text
"at least 4.0 ml"
, Text
"over four milliliters"
, Text
"more than four mls"
]
]