{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.KO.Corpus
( corpus ) where
import Prelude
import Data.String
import Duckling.Locale
import Duckling.Numeral.Types
import Duckling.Resolve
import Duckling.Testing.Types
corpus :: Corpus
corpus :: Corpus
corpus = (Context
testContext {locale :: Locale
locale = Lang -> Maybe Region -> Locale
makeLocale Lang
KO 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
[ NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
0)
[ Text
"0"
, Text
"영"
, Text
"빵"
, Text
"공"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
1)
[ Text
"1"
, Text
"일"
, Text
"하나"
, Text
"한"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
10)
[ Text
"10"
, Text
"십"
, Text
"열"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
11)
[ Text
"11"
, Text
"십일"
, Text
"열하나"
, Text
"십하나"
, Text
"열한"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
20)
[ Text
"20"
, Text
"이십"
, Text
"스물"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
35)
[ Text
"35"
, Text
"삼십오"
, Text
"서른다섯"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
47)
[ Text
"47"
, Text
"사십칠"
, Text
"마흔일곱"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
52)
[ Text
"52"
, Text
"오십이"
, Text
"쉰둘"
, Text
"쉰두"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
69)
[ Text
"69"
, Text
"육십구"
, Text
"예순아홉"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
71)
[ Text
"71"
, Text
"칠십일"
, Text
"일흔하나"
, Text
"일흔한"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
84)
[ Text
"84"
, Text
"팔십사"
, Text
"여든넷"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
93)
[ Text
"93"
, Text
"구십삼"
, Text
"아흔셋"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
100)
[ Text
"100"
, Text
"백"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
123)
[ Text
"123"
, Text
"백이십삼"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
579)
[ Text
"579"
, Text
"오백칠십구"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
1000)
[ Text
"1000"
, Text
"천"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
1723)
[ Text
"1723"
, Text
"천칠백이십삼"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
5619)
[ Text
"5619"
, Text
"오천육백십구"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
10000)
[ Text
"10000"
, Text
"만"
, Text
"일만"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
12345)
[ Text
"12345"
, Text
"만이천삼백사십오"
, Text
"일만이천삼백사십오"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
58194)
[ Text
"58194"
, Text
"오만팔천백구십사"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
581900)
[ Text
"581900"
, Text
"오십팔만천구백"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
5819014)
[ Text
"5819014"
, Text
"오백팔십일만구천십사"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
58190148)
[ Text
"58190148"
, Text
"오천팔백십구만백사십팔"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
100000000)
[ Text
"100000000"
, Text
"일억"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
274500000000)
[ Text
"274500000000"
, Text
"이천칠백사십오억"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
100000002)
[ Text
"100000002"
, Text
"일억이"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
27350000)
[ Text
"27350000"
, Text
"이천칠백삼십오만"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
3235698120)
[ Text
"3235698120"
, Text
"삼십이억삼천오백육십구만팔천백이십"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
40234985729)
[ Text
"40234985729"
, Text
"사백이억삼천사백구십팔만오천칠백이십구"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
701239801123)
[ Text
"701239801123"
, Text
"칠천십이억삼천구백팔십만천백이십삼"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
3.4)
[ Text
"3.4"
, Text
"삼점사"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
4123.3)
[ Text
"4123.3"
, Text
"사천백이십삼점삼"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
1.23)
[ Text
"일점이삼"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue (-Double
3))
[ Text
"-3"
, Text
"마이너스3"
, Text
"마이너스삼"
, Text
"마이너스 3"
, Text
"마이나스3"
, Text
"마이나스 3"
]
, NumeralValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Double -> NumeralValue
NumeralValue Double
0.75)
[ Text
"3/4"
, Text
"사분의삼"
]
]