{-# LANGUAGE OverloadedStrings #-}
module Duckling.Time.PT.Corpus
( corpus
, negativeCorpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types hiding (examples)
import Duckling.Time.Corpus
import Duckling.Time.Types hiding (Month)
import Duckling.TimeGrain.Types hiding (add)
corpus :: Corpus
corpus :: Corpus
corpus = (Context
testContext {locale :: Locale
locale = Lang -> Maybe Region -> Locale
makeLocale Lang
PT Maybe Region
forall a. Maybe a
Nothing}, Options
testOptions, [Example]
allExamples)
negativeCorpus :: NegativeCorpus
negativeCorpus :: NegativeCorpus
negativeCorpus = (Context
testContext {locale :: Locale
locale = Lang -> Maybe Region -> Locale
makeLocale Lang
PT Maybe Region
forall a. Maybe a
Nothing}, Options
testOptions, [Text]
examples)
where
examples :: [Text]
examples =
[ Text
"no 987"
, Text
"um"
, Text
"um dos"
, Text
"um dos minutos"
, Text
"ter"
]
allExamples :: [Example]
allExamples :: [Example]
allExamples = [[Example]] -> [Example]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
4, Int
30, Pico
0) Grain
Second)
[ Text
"agora"
, Text
"já"
, Text
"ja"
, Text
"nesse instante"
, Text
"neste instante"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"hoje"
, Text
"nesse momento"
, Text
"neste momento"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
11, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"ontem"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
10, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"antes de ontem"
, Text
"anteontem"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
13, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"amanhã"
, Text
"amanha"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
14, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"depois de amanhã"
, Text
"depois de amanha"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
18, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"segunda-feira"
, Text
"segunda feira"
, Text
"segunda"
, Text
"seg."
, Text
"seg"
, Text
"essa segunda-feira"
, Text
"essa segunda feira"
, Text
"essa segunda"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
18, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"segunda, 18 de fevereiro"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
19, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"terça-feira"
, Text
"terça feira"
, Text
"terça"
, Text
"terca-feira"
, Text
"terca feira"
, Text
"terca"
, Text
"ter."
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
13, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"quarta-feira"
, Text
"quarta feira"
, Text
"quarta"
, Text
"qua."
, Text
"qua"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
14, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"quinta-feira"
, Text
"quinta feira"
, Text
"quinta"
, Text
"qui."
, Text
"qui"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
15, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"sexta-feira"
, Text
"sexta feira"
, Text
"sexta"
, Text
"sex."
, Text
"sex"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
16, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"sábado"
, Text
"sabado"
, Text
"sáb."
, Text
"sáb"
, Text
"sab."
, Text
"sab"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
17, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"domingo"
, Text
"dom."
, Text
"dom"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
5, Int
5, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"5 de maio"
, Text
"cinco de maio"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
5, Int
5, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"cinco de maio de 2013"
, Text
"5 de maio de 2013"
, Text
"5/5"
, Text
"5/5/2013"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
7, Int
4, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"4 de julho"
, Text
"quatro de julho"
, Text
"4/7"
, Text
"4/7/2013"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
3, Int
3, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"3 de março"
, Text
"três de março"
, Text
"tres de março"
, Text
"3/3"
, Text
"3/3/2013"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
4, Int
5, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"5 de abril"
, Text
"cinco de abril"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
3, Int
1, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"1 de março"
, Text
"primeiro de março"
, Text
"um de março"
, Text
"1o de março"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
3, Int
1, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"1-3-2013"
, Text
"1.3.2013"
, Text
"1/3/2013"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
16, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"essa dia 16"
, Text
"16 de fevereiro"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
17, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"este dia 17"
, Text
"17 de fevereiro"
, Text
"17/2"
, Text
"no domingo"
, Text
"no dia 17"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
20, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"esse dia 20"
, Text
"20 de fevereiro"
, Text
"20/2"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
1974, Int
10, Int
31, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"31/10/1974"
, Text
"31/10/74"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
19, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"próxima terça-feira"
, Text
"próxima terça feira"
, Text
"próxima terça"
, Text
"proxima terça-feira"
, Text
"proxima terça feira"
, Text
"proxima terça"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
20, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"quarta que vem"
, Text
"quarta da semana que vem"
, Text
"quarta da próxima semana"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"terça desta semana"
, Text
"terça dessa semana"
, Text
"terça agora"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
11, Int
0, Int
0, Pico
0) Grain
Week)
[ Text
"esta semana"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
4, Int
0, Int
0, Pico
0) Grain
Week)
[ Text
"semana passada"
, Text
"semana anterior"
, Text
"passada semana"
, Text
"anterior semana"
, Text
"última semana"
, Text
"ultima semana"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
18, Int
0, Int
0, Pico
0) Grain
Week)
[ Text
"semana que vem"
, Text
"proxima semana"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
1, Int
0, Int
0, Int
0, Pico
0) Grain
Month)
[ Text
"mês passado"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
3, Int
0, Int
0, Int
0, Pico
0) Grain
Month)
[ Text
"mes que vem"
, Text
"próximo mês"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2012, Int
0, Int
0, Int
0, Int
0, Pico
0) Grain
Year)
[ Text
"ano passado"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
0, Int
0, Int
0, Int
0, Pico
0) Grain
Year)
[ Text
"este ano"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2014, Int
0, Int
0, Int
0, Int
0, Pico
0) Grain
Year)
[ Text
"ano que vem"
, Text
"proximo ano"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
10, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"domingo passado"
, Text
"domingo da semana passada"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
5, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"terça passada"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
15, Int
0, Pico
0) Grain
Hour)
[ Text
"às tres da tarde"
, Text
"às tres"
, Text
"às 3 pm"
, Text
"às 15 horas"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
20, Int
0, Pico
0) Grain
Hour)
[ Text
"às oito da noite"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
15, Int
0, Pico
0) Grain
Minute)
[ Text
"15:00"
, Text
"15.00"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
13, Int
0, Int
0, Pico
0) Grain
Hour)
[ Text
"meianoite"
, Text
"meia noite"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
12, Int
0, Pico
0) Grain
Hour)
[ Text
"meio dia"
, Text
"meiodia"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
12, Int
15, Pico
0) Grain
Minute)
[ Text
"meio dia e quinze"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
11, Int
55, Pico
0) Grain
Minute)
[ Text
"5 para meio dia"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
12, Int
30, Pico
0) Grain
Minute)
[ Text
"meio dia e meia"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
6, Int
0, Pico
0) Grain
Hour)
[ Text
"as seis da manha"
, Text
"as seis pela manha"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
15, Int
15, Pico
0) Grain
Minute)
[ Text
"às tres e quinze"
, Text
"às tres e quinze da tarde"
, Text
"às tres e quinze pela tarde"
, Text
"15:15"
, Text
"15.15"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
15, Int
30, Pico
0) Grain
Minute)
[ Text
"às tres e meia"
, Text
"às 3 e trinta"
, Text
"às tres e meia da tarde"
, Text
"às 3 e trinta da tarde"
, Text
"15:30"
, Text
"15.30"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
11, Int
45, Pico
0) Grain
Minute)
[ Text
"quinze para meio dia"
, Text
"quinze para o meio dia"
, Text
"11:45"
, Text
"as onze e quarenta e cinco"
, Text
"hoje quinze para o meio dia"
, Text
"hoje às onze e quarenta e cinco"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
5, Int
15, Pico
0) Grain
Minute)
[ Text
"5 e quinze"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
6, Int
0, Pico
0) Grain
Hour)
[ Text
"6 da manhã"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
13, Int
11, Int
0, Pico
0) Grain
Hour)
[ Text
"quarta às onze da manhã"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2014, Int
9, Int
12, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"sexta, 12 de setembro de 2014"
, Text
"sexta feira, 12 de setembro de 2014"
, Text
"12 de setembro de 2014, sexta"
, Text
"12 de setembro de 2014 sexta feira"
, Text
"sexta feira 12 de setembro de 2014"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
4, Int
30, Pico
1) Grain
Second)
[ Text
"em um segundo"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
4, Int
31, Pico
0) Grain
Second)
[ Text
"em um minuto"
, Text
"em 1 min"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
4, Int
32, Pico
0) Grain
Second)
[ Text
"em 2 minutos"
, Text
"em dois minutos"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
5, Int
30, Pico
0) Grain
Second)
[ Text
"em 60 minutos"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
5, Int
30, Pico
0) Grain
Minute)
[ Text
"em uma hora"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
2, Int
30, Pico
0) Grain
Minute)
[ Text
"fazem duas horas"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
13, Int
4, Int
30, Pico
0) Grain
Minute)
[ Text
"em 24 horas"
, Text
"em vinte e quatro horas"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
13, Int
4, Int
0, Pico
0) Grain
Hour)
[ Text
"em um dia"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
19, Int
4, Int
0, Pico
0) Grain
Hour)
[ Text
"em 7 dias"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
19, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"em uma semana"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
1, Int
22, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"faz tres semanas"
, Text
"faz três semanas"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
4, Int
12, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"em dois meses"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2012, Int
11, Int
12, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"faz tres meses"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2014, Int
2, Int
0, Int
0, Int
0, Pico
0) Grain
Month)
[ Text
"em um ano"
, Text
"em 1 ano"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2011, Int
2, Int
0, Int
0, Int
0, Pico
0) Grain
Month)
[ Text
"faz dois anos"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
6, Int
21, Int
0, Int
0, Pico
0), (Integer
2013, Int
9, Int
24, Int
0, Int
0, Pico
0)) Grain
Day)
[ Text
"este verão"
, Text
"este verao"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2012, Int
12, Int
21, Int
0, Int
0, Pico
0), (Integer
2013, Int
3, Int
21, Int
0, Int
0, Pico
0)) Grain
Day)
[ Text
"este inverno"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
12, Int
25, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"Natal"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
12, Int
31, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"véspera de ano novo"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2014, Int
1, Int
1, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"ano novo"
, Text
"reveillon"
, Text
"Reveillon"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
12, Int
18, Int
0, Pico
0), (Integer
2013, Int
2, Int
13, Int
0, Int
0, Pico
0)) Grain
Hour)
[ Text
"esta noite"
, Text
"essa noite"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
13, Int
18, Int
0, Pico
0), (Integer
2013, Int
2, Int
14, Int
0, Int
0, Pico
0)) Grain
Hour)
[ Text
"amanhã a noite"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
11, Int
18, Int
0, Pico
0), (Integer
2013, Int
2, Int
12, Int
0, Int
0, Pico
0)) Grain
Hour)
[ Text
"ontem a noite"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
15, Int
18, Int
0, Pico
0), (Integer
2013, Int
2, Int
18, Int
0, Int
0, Pico
0)) Grain
Hour)
[ Text
"este final de semana"
, Text
"este fim de semana"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
18, Int
4, Int
0, Pico
0), (Integer
2013, Int
2, Int
18, Int
12, Int
0, Pico
0)) Grain
Hour)
[ Text
"segunda de manhã"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
15, Int
4, Int
0, Pico
0), (Integer
2013, Int
2, Int
15, Int
12, Int
0, Pico
0)) Grain
Hour)
[ Text
"dia 15 de fevereiro pela manhã"
, Text
"dia 15 de fevereiro de manhã"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
20, Int
0, Pico
0) Grain
Hour)
[ Text
"às 8 da noite"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
12, Int
4, Int
29, Pico
58), (Integer
2013, Int
2, Int
12, Int
4, Int
30, Pico
0)) Grain
Second)
[ Text
"2 segundos atras"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
12, Int
4, Int
30, Pico
1), (Integer
2013, Int
2, Int
12, Int
4, Int
30, Pico
4)) Grain
Second)
[ Text
"proximos 3 segundos"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
12, Int
4, Int
28, Pico
0), (Integer
2013, Int
2, Int
12, Int
4, Int
30, Pico
0)) Grain
Minute)
[ Text
"2 minutos atrás"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
12, Int
4, Int
31, Pico
0), (Integer
2013, Int
2, Int
12, Int
4, Int
34, Pico
0)) Grain
Minute)
[ Text
"proximos 3 minutos"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
12, Int
5, Int
0, Pico
0), (Integer
2013, Int
2, Int
12, Int
8, Int
0, Pico
0)) Grain
Hour)
[ Text
"proximas 3 horas"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
10, Int
0, Int
0, Pico
0), (Integer
2013, Int
2, Int
12, Int
0, Int
0, Pico
0)) Grain
Day)
[ Text
"passados 2 dias"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
13, Int
0, Int
0, Pico
0), (Integer
2013, Int
2, Int
16, Int
0, Int
0, Pico
0)) Grain
Day)
[ Text
"proximos 3 dias"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
1, Int
28, Int
0, Int
0, Pico
0), (Integer
2013, Int
2, Int
11, Int
0, Int
0, Pico
0)) Grain
Week)
[ Text
"duas semanas atras"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
18, Int
0, Int
0, Pico
0), (Integer
2013, Int
3, Int
11, Int
0, Int
0, Pico
0)) Grain
Week)
[ Text
"3 proximas semanas"
, Text
"3 semanas que vem"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2012, Int
12, Int
0, Int
0, Int
0, Pico
0), (Integer
2013, Int
2, Int
0, Int
0, Int
0, Pico
0)) Grain
Month)
[ Text
"passados 2 meses"
, Text
"últimos 2 meses"
, Text
"2 meses anteriores"
, Text
"2 últimos meses"
, Text
"2 anteriores meses"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
3, Int
0, Int
0, Int
0, Pico
0), (Integer
2013, Int
6, Int
0, Int
0, Int
0, Pico
0)) Grain
Month)
[ Text
"3 próximos meses"
, Text
"proximos tres meses"
, Text
"tres meses que vem"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2011, Int
0, Int
0, Int
0, Int
0, Pico
0), (Integer
2013, Int
0, Int
0, Int
0, Int
0, Pico
0)) Grain
Year)
[ Text
"passados 2 anos"
, Text
"últimos 2 anos"
, Text
"2 anos anteriores"
, Text
"2 últimos anos"
, Text
"2 anteriores anos"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2014, Int
0, Int
0, Int
0, Int
0, Pico
0), (Integer
2017, Int
0, Int
0, Int
0, Int
0, Pico
0)) Grain
Year)
[ Text
"3 próximos anos"
, Text
"proximo tres anos"
, Text
"3 anos que vem"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
7, Int
13, Int
0, Int
0, Pico
0), (Integer
2013, Int
7, Int
16, Int
0, Int
0, Pico
0)) Grain
Day)
[ Text
"13 a 15 de julho"
, Text
"13 - 15 de julho de 2013"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
12, Int
9, Int
30, Pico
0), (Integer
2013, Int
2, Int
12, Int
11, Int
1, Pico
0)) Grain
Minute)
[ Text
"9:30 - 11:00"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
12, Int
21, Int
0, Int
0, Pico
0), (Integer
2014, Int
1, Int
7, Int
0, Int
0, Pico
0)) Grain
Day)
[ Text
"21 de Dez. a 6 de Jan"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
2, Int
12, Int
4, Int
30, Pico
0), (Integer
2013, Int
2, Int
12, Int
7, Int
30, Pico
0)) Grain
Second)
[ Text
"dentro de tres horas"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
16, Int
0, Pico
0) Grain
Hour)
[ Text
"as quatro da tarde"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
13, Int
0, Pico
0) Grain
Minute)
[ Text
"as quatro CET"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (IntervalDirection -> Datetime -> Grain -> Context -> TimeValue
datetimeOpenInterval IntervalDirection
After (Integer
2013, Int
2, Int
12, Int
12, Int
0, Pico
0) Grain
Hour)
[ Text
"após ao meio dia"
, Text
"depois do meio dia"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (IntervalDirection -> Datetime -> Grain -> Context -> TimeValue
datetimeOpenInterval IntervalDirection
Before (Integer
2013, Int
2, Int
12, Int
12, Int
0, Pico
0) Grain
Hour)
[ Text
"antes do meio dia"
, Text
"não mais que meio dia"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (IntervalDirection -> Datetime -> Grain -> Context -> TimeValue
datetimeOpenInterval IntervalDirection
After (Integer
2013, Int
2, Int
13, Int
15, Int
0, Pico
0) Grain
Hour)
[ Text
"amanhã depois das 15hs"
, Text
"amanha após as quinze horas"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (IntervalDirection -> Datetime -> Grain -> Context -> TimeValue
datetimeOpenInterval IntervalDirection
Before (Integer
2013, Int
2, Int
13, Int
0, Int
0, Pico
0) Grain
Hour)
[ Text
"antes da meia noite"
, Text
"até a meia noite"
]
,(Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
12, Int
3, Int
0, Pico
0) Grain
Hour)
[ Text
"última hora"
, Text
"hora anterior"
, Text
"hora passada"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
1, Int
1, Int
0, Int
0, Pico
0) Grain
Quarter)
[ Text
"este trimestre"
, Text
"trimestre actual"
, Text
"trimestre atual"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
1, Int
1, Int
0, Int
0, Pico
0) Grain
Month)
[ Text
"primeiro mês de 2013"
, Text
"primeiro mês 2013"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
4, Int
1, Int
0, Int
0, Pico
0) Grain
Quarter)
[ Text
"próximo trimestre"
, Text
"segundo trimestre de 2013"
, Text
"segundo trimestre"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
7, Int
1, Int
0, Int
0, Pico
0) Grain
Quarter)
[ Text
"terceiro trimestre"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2018, Int
10, Int
1, Int
0, Int
0, Pico
0) Grain
Quarter)
[ Text
"quarto trimestre de 2018"
, Text
"quarto trimestre 2018"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2012, Int
10, Int
1, Int
0, Int
0, Pico
0) Grain
Quarter)
[ Text
"trimestre passado"
, Text
"trimestre anterior"
, Text
"último trimestre"
, Text
"ultimo trimestre"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
12, Int
1, Int
0, Int
0, Pico
0) Grain
Month)
[ Text
"décimo segundo mês de 2013"
, Text
"último mês de 2013"
, Text
"último mês 2013"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2015, Int
10, Int
1, Int
0, Int
0, Pico
0) Grain
Quarter)
[ Text
"último trimestre de 2015"
, Text
"último trimestre 2015"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
7, Int
13, Int
0, Int
0, Pico
0), (Integer
2013, Int
7, Int
16, Int
0, Int
0, Pico
0)) Grain
Day)
[ Text
"desde 13 a 15 de Julho"
, Text
"a partir de 13 até 15 de Julho"
, Text
"desde 13 até 15 de Julho"
, Text
"13-15 de Julho"
, Text
"13 até 15 de Julho"
, Text
"13 a 15 de Julho"
, Text
"desde 13 a 15 Julho"
, Text
"a partir de 13 até 15 Julho"
, Text
"desde 13 até 15 Julho"
, Text
"13-15 Julho"
, Text
"13 até 15 Julho"
, Text
"13 a 15 Julho"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
1, Int
1, Int
0, Int
0, Pico
0), (Integer
2017, Int
10, Int
1, Int
0, Int
0, Pico
0)) Grain
Quarter)
[ Text
"de primeiro trimestre de 2017 até terceiro trimestre de 2017"
, Text
"de primeiro trimestre de 2017 até ao terceiro trimestre de 2017"
, Text
"do primeiro trimestre de 2017 até terceiro trimestre de 2017"
, Text
"do primeiro trimestre de 2017 até ao terceiro trimestre de 2017"
, Text
"desde primeiro trimestre de 2017 até terceiro trimestre de 2017"
, Text
"desde primeiro trimestre de 2017 até ao terceiro trimestre de 2017"
, Text
"a partir do primeiro trimestre de 2017 até terceiro trimestre de 2017"
, Text
"a partir do primeiro trimestre de 2017 até ao terceiro trimestre de 2017"
, Text
"a partir de primeiro trimestre de 2017 até terceiro trimestre de 2017"
, Text
"a partir de primeiro trimestre de 2017 até ao terceiro trimestre de 2017"
, Text
"primeiro trimestre de 2017 a terceiro trimestre de 2017"
, Text
"primeiro trimestre de 2017 ao terceiro trimestre de 2017"
, Text
"primeiro trimestre de 2017 - terceiro trimestre de 2017"
, Text
"entre primeiro trimestre de 2017 e terceiro trimestre de 2017"
, Text
"entre o primeiro trimestre de 2017 e terceiro trimestre de 2017"
, Text
"primeiro trimestre de 2017 até terceiro trimestre de 2017"
, Text
"primeiro trimestre de 2017 até ao terceiro trimestre de 2017"
, Text
"primeiro trimestre 2017 a terceiro trimestre 2017"
, Text
"primeiro trimestre 2017 ao terceiro trimestre 2017"
, Text
"primeiro trimestre 2017 - terceiro trimestre 2017"
, Text
"primeiro trimestre 2017 até terceiro trimestre 2017"
, Text
"primeiro trimestre 2017 até ao terceiro trimestre 2017"
, Text
"entre primeiro trimestre 2017 e terceiro trimestre 2017"
, Text
"entre o primeiro trimestre 2017 e terceiro trimestre 2017"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
3, Int
1, Int
0, Int
0, Pico
0), (Integer
2017, Int
10, Int
1, Int
0, Int
0, Pico
0)) Grain
Month)
[ Text
"de terceiro mês de 2017 até nono mês de 2017"
, Text
"de terceiro mês de 2017 até ao nono mês de 2017"
, Text
"do terceiro mês de 2017 até nono mês de 2017"
, Text
"do terceiro mês de 2017 até ao nono mês de 2017"
, Text
"desde terceiro mês de 2017 até nono mês de 2017"
, Text
"desde terceiro mês de 2017 até ao nono mês de 2017"
, Text
"a partir do terceiro mês de 2017 até nono mês de 2017"
, Text
"a partir do terceiro mês de 2017 até ao nono mês de 2017"
, Text
"a partir de terceiro mês de 2017 até nono mês de 2017"
, Text
"a partir de terceiro mês de 2017 até ao nono mês de 2017"
, Text
"terceiro mês de 2017 a nono mês de 2017"
, Text
"terceiro mês de 2017 ao nono mês de 2017"
, Text
"terceiro mês de 2017 - nono mês de 2017"
, Text
"entre terceiro mês de 2017 e nono mês de 2017"
, Text
"entre o terceiro mês de 2017 e nono mês de 2017"
, Text
"terceiro mês de 2017 até nono mês de 2017"
, Text
"terceiro mês de 2017 até ao nono mês de 2017"
, Text
"terceiro mês 2017 a nono mês 2017"
, Text
"terceiro mês 2017 ao nono mês 2017"
, Text
"terceiro mês 2017 - nono mês 2017"
, Text
"terceiro mês 2017 até nono mês 2017"
, Text
"terceiro mês 2017 até ao nono mês 2017"
, Text
"entre terceiro mês 2017 e nono mês 2017"
, Text
"entre o terceiro mês 2017 e nono mês 2017"
]
]