{-# LANGUAGE OverloadedStrings #-}
module Duckling.Volume.DE.Corpus
( corpus ) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types
import Duckling.Volume.Types
corpus :: Corpus
corpus :: Corpus
corpus = (Context
testContext {locale :: Locale
locale = Lang -> Maybe Region -> Locale
makeLocale Lang
DE Maybe Region
forall a. Maybe a
Nothing}, 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"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Litre Double
2)
[ Text
"2 liter"
, Text
"2l"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Litre Double
1000)
[ Text
"1000 liter"
, Text
"tausend liter"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Litre Double
0.5)
[ Text
"halber liter"
, Text
"ein halber liter"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Litre Double
0.25)
[ Text
"viertel liter"
, Text
"ein viertel liter"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Millilitre Double
1)
[ Text
"ein milliliter"
, Text
"ein ml"
, Text
"1ml"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Millilitre Double
250)
[ Text
"250 milliliter"
, Text
"250ml"
, Text
"250 ml"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
simple Unit
Hectolitre Double
3)
[ Text
"3 hektoliter"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> (Double, Double) -> VolumeValue
between Unit
Litre (Double
100,Double
1000))
[ Text
"zwischen 100 und 1000 litern"
, Text
"100-1000 liter"
, Text
"von 100 bis 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
"etwa 2 -7 l"
, Text
"~2-7 liter"
, Text
"von 2 bis 7 l"
, Text
"zwischen 2,0 l und ungefähr 7,0 l"
, Text
"zwischen 2l und etwa 7l"
, Text
"2 - ~7 liter"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
under Unit
Hectolitre Double
2)
[ Text
"nicht mehr als 2 hektoliter"
, Text
"höchstens zwei hektoliter"
, Text
"unter 2 hektolitern"
, Text
"weniger als 2 hektoliter"
]
, VolumeValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Unit -> Double -> VolumeValue
above Unit
Millilitre Double
4)
[ Text
"mehr als 4 ml"
, Text
"wenigstens 4,0 ml"
, Text
"über vier milliliter"
, Text
"mindestens vier ml"
]
]