-- 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. {-# LANGUAGE GADTs #-} {-# LANGUAGE NoRebindableSyntax #-} {-# LANGUAGE OverloadedStrings #-} module Duckling.Time.NL.Rules ( rules ) where import Data.Text (Text) import Prelude import qualified Data.Text as Text import Duckling.Dimensions.Types import Duckling.Duration.Helpers (duration, isGrain) 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.HolidayHelpers 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 ruleInstants :: [Rule] ruleInstants = mkRuleInstants [ ( "now" , TG.Second, 0, "meteen|nu|direct|zojuist" ) , ( "today" , TG.Day , 0, "vandaag|op deze dag" ) , ( "tomorrow" , TG.Day , 1, "morgen" ) , ( "yesterday" , TG.Day , -1, "gisteren" ) , ( "after tomorrow" , TG.Day , 2, "overmorgen" ) , ( "before yesterday", TG.Day , -2, "eergisteren" ) , ( "EOM|End of month", TG.Month , 1, "(het )?einde? van de maand" ) , ( "EOY|End of year" , TG.Year , 1, "(het )? einde? van het jaar" ) ] ruleDaysOfWeek :: [Rule] ruleDaysOfWeek = mkRuleDaysOfWeek [ ( "monday" , "maandags?|ma\\." ) , ( "tuesday" , "dinsdags?|di\\." ) , ( "wednesday" , "woensdags?|woe\\." ) , ( "thursday" , "donderdags?|do\\." ) , ( "friday" , "vrijdags?|vr(ij)?\\." ) , ( "saturday" , "zaterdags?|zat?\\." ) , ( "sunday" , "zondags?|zon?\\." ) ] ruleMonths :: [Rule] ruleMonths = mkRuleMonths [ ( "January" , "januari|jan\\.?" ) , ( "February" , "februari|feb\\.?" ) , ( "March" , "maart|mar\\.?" ) , ( "April" , "april|apr\\.?" ) , ( "May" , "mei\\.?" ) , ( "June" , "juni?\\.?" ) , ( "July" , "juli?\\.?" ) , ( "August" , "augustus|aug\\.?" ) , ( "September", "september|sept?\\.?" ) , ( "October" , "oktober|okt\\.?" ) , ( "November" , "november|nov\\.?" ) , ( "December" , "december|dec\\.?" ) ] ruleSeasons :: [Rule] ruleSeasons = mkRuleSeasons [ ( "summer" , "zomer" , monthDay 6 21, monthDay 9 23 ) , ( "fall" , "herfst|najaar" , monthDay 9 23, monthDay 12 21 ) , ( "winter" , "winter" , monthDay 12 21, monthDay 3 20 ) , ( "spring" , "lente|voorjaar" , monthDay 3 20, monthDay 6 21 ) ] ruleHolidays :: [Rule] ruleHolidays = mkRuleHolidays [ ( "Nieuwjaarsdag", "nieuwjaars?(dag)?", monthDay 1 1 ) , ( "Valentijnsdag", "valentijns?(dag)?", monthDay 2 14 ) , ( "Halloween", "hall?oween?", monthDay 10 31 ) , ( "Allerheiligen", "allerheiligen?|aller heiligen?", monthDay 11 1 ) , ( "Kerstavond", "kerstavond", monthDay 12 24 ) , ( "Tweede Kerstdag", "tweede kerstdag", monthDay 12 26 ) , ( "Kerstmis", "kerstmis|(eerste )?kerstdag|kerst", monthDay 12 25 ) , ( "Oudjaar", "oudjaar|oudejaars?avond", monthDay 12 31 ) , ( "Moederdag", "moederdag", nthDOWOfMonth 2 7 5 ) , ( "Vaderdag", "vaderdag", nthDOWOfMonth 3 7 6 ) ] ruleComputedHolidays' :: [Rule] ruleComputedHolidays' = mkRuleHolidays' [ ( "Koningsdag", "king's day|koningsdag" , computeKingsDay ) ] ruleRelativeMinutesToOrAfterIntegerPartOfDay :: Rule ruleRelativeMinutesToOrAfterIntegerPartOfDay = Rule { name = "relative minutes to|till|before|after (time-of-day)" , pattern = [ Predicate $ isIntegerBetween 1 59 , regex "(voor|over|na)" , Predicate isATimeOfDay ] , prod = \tokens -> case tokens of (Token Numeral NumeralData{TNumeral.value = v}: Token RegexMatch (GroupMatch (match:_)): Token Time td: _) -> case Text.toLower match of "voor" -> tt $ durationBefore (duration TG.Minute $ floor v) td _ -> tt $ durationAfter (duration TG.Minute $ floor v) td _ -> Nothing } ruleQuarterTotillbeforeIntegerHourofday :: Rule ruleQuarterTotillbeforeIntegerHourofday = Rule { name = "quarter to|till|before (hour-of-day)" , pattern = [ regex "kwart(ier)? voor" , Predicate isAnHourOfDay ] , prod = \tokens -> case tokens of (_:Token Time td:_) -> Token Time <$> minutesBefore 15 td _ -> Nothing } ruleHalfTotillbeforeIntegerHourofday :: Rule ruleHalfTotillbeforeIntegerHourofday = Rule { name = "half to|till|before (hour-of-day)" , pattern = [ regex "half" , Predicate isAnHourOfDay ] , prod = \tokens -> case tokens of (_:Token Time td:_) -> Token Time <$> minutesBefore 30 td _ -> Nothing } ruleTheOrdinalCycleOfTime :: Rule ruleTheOrdinalCycleOfTime = Rule { name = "the of