-- Copyright (c) 2016-present, Facebook, Inc. -- All rights reserved. -- -- This source code is licensed under the BSD-style license found in the -- LICENSE file in the root directory of this source tree. An additional grant -- of patent rights can be found in the PATENTS file in the same directory. {-# LANGUAGE GADTs #-} {-# LANGUAGE NoRebindableSyntax #-} {-# LANGUAGE OverloadedStrings #-} module Duckling.Time.IT.Rules ( rules ) where import Data.Text (Text) import Prelude import qualified Data.Text as Text import Duckling.Dimensions.Types import Duckling.Numeral.Helpers (parseInt) import Duckling.Numeral.Types (NumeralData(..)) import Duckling.Ordinal.Types (OrdinalData(..)) import Duckling.Regex.Types import Duckling.Time.Helpers import Duckling.Time.Types (TimeData (..)) import Duckling.Types import qualified Duckling.Numeral.Types as TNumeral import qualified Duckling.Ordinal.Types as TOrdinal import qualified Duckling.Time.Types as TTime import qualified Duckling.TimeGrain.Types as TG ruleFestaDellaRepubblica :: Rule ruleFestaDellaRepubblica = Rule { name = "festa della repubblica" , pattern = [ regex "((festa del)?la )?repubblica" ] , prod = \_ -> tt $ monthDay 6 2 } ruleEpifania :: Rule ruleEpifania = Rule { name = "epifania" , pattern = [ regex "(epifania|befana)" ] , prod = \_ -> tt $ monthDay 1 6 } ruleDayofmonthNamedmonth :: Rule ruleDayofmonthNamedmonth = Rule { name = " " , pattern = [ Predicate isDOMInteger , Predicate isAMonth ] , prod = \tokens -> case tokens of (token:Token Time td:_) -> Token Time <$> intersectDOM td token _ -> Nothing } ruleTheDayAfterTomorrow :: Rule ruleTheDayAfterTomorrow = Rule { name = "the day after tomorrow" , pattern = [ regex "(il giorno )?dopo\\s?domani" ] , prod = \_ -> tt $ cycleNth TG.Day 2 } ruleInafterDuration :: Rule ruleInafterDuration = Rule { name = "in/after " , pattern = [ regex "[tf]ra|in|dopo" , dimension Duration ] , prod = \tokens -> case tokens of (_:Token Duration dd:_) -> tt $ inDuration dd _ -> Nothing } ruleTheLastCycle :: Rule ruleTheLastCycle = Rule { name = "the last " , pattern = [ regex "(([nd]el)?l' ?ultim|(il|la) passat|([nd]el)?l[ao] scors)[oa]" , dimension TimeGrain ] , prod = \tokens -> case tokens of (_:Token TimeGrain grain:_) -> tt . cycleNth grain $ - 1 _ -> Nothing } ruleStanotte :: Rule ruleStanotte = Rule { name = "stanotte" , pattern = [ regex "(sta|nella )notte|(in|nella) nottata" ] , prod = \_ -> do let td1 = cycleNth TG.Day 1 td2 <- interval TTime.Open (hour False 0) (hour False 4) Token Time . partOfDay <$> intersect td1 td2 } ruleDomattina :: Rule ruleDomattina = Rule { name = "domattina" , pattern = [ regex "domattina" ] , prod = \_ -> do let td1 = cycleNth TG.Day 1 td2 <- interval TTime.Open (hour False 4) (hour False 12) Token Time . partOfDay <$> intersect td1 td2 } ruleTheCycleNext :: Rule ruleTheCycleNext = Rule { name = "the next" , pattern = [ regex "l'|il|la|[nd]el(la)?" , dimension TimeGrain , regex "prossim[oa]" ] , prod = \tokens -> case tokens of (_:Token TimeGrain grain:_) -> tt $ cycleNth grain 1 _ -> Nothing } ruleCycleNext :: Rule ruleCycleNext = Rule { name = " next" , pattern = [ dimension TimeGrain , regex "prossim[oa]" ] , prod = \tokens -> case tokens of (Token TimeGrain grain:_) -> tt $ cycleNth grain 1 _ -> Nothing } ruleFestaDellaLiberazione :: Rule ruleFestaDellaLiberazione = Rule { name = "festa della liberazione" , pattern = [ regex "((festa|anniversario) della|(al)?la) liberazione" ] , prod = \_ -> tt $ monthDay 4 25 } ruleStamattina :: Rule ruleStamattina = Rule { name = "stamattina" , pattern = [ regex "stamattina" ] , prod = \_ -> do let td1 = cycleNth TG.Day 0 td2 <- interval TTime.Open (hour False 4) (hour False 12) Token Time . partOfDay <$> intersect td1 td2 } ruleYearNotLatent :: Rule ruleYearNotLatent = Rule { name = "year (1000-2100 not latent)" , pattern = [ Predicate $ isIntegerBetween 1000 2100 ] , prod = \tokens -> case tokens of (token:_) -> do v <- getIntValue token tt $ year v _ -> Nothing } ruleValentinesDay :: Rule ruleValentinesDay = Rule { name = "valentine's day" , pattern = [ regex "san valentino|festa degli innamorati" ] , prod = \_ -> tt $ monthDay 2 14 } ruleTheOrdinalCycleOfTime :: Rule ruleTheOrdinalCycleOfTime = Rule { name = "the of