-- 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.DE.Rules ( rules ) where import Prelude import Data.Text (Text) import qualified Data.Text as Text import Duckling.Dimensions.Types import Duckling.Numeral.Helpers (parseInt) import Duckling.Ordinal.Types (OrdinalData (..)) import Duckling.Regex.Types import Duckling.Time.Helpers import Duckling.Time.Types (TimeData (..)) import Duckling.Types 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, "(genau)? ?jetzt|diesen moment|in diesem moment|gerade eben" ) , ( "today" , TG.Day , 0, "heute|(um diese zeit|zu dieser zeit|um diesen zeitpunkt|zu diesem zeitpunkt)" ) , ( "tomorrow" , TG.Day , 1, "morgen" ) , ( "yesterday" , TG.Day , -1, "gestern" ) , ( "after tomorrow" , TG.Day , 2, "(ü)bermorgen" ) , ( "before yesterday", TG.Day , -2, "vorgestern" ) , ( "EOM|End of month", TG.Month , 1, "(das )?ende des monats?" ) , ( "EOY|End of year" , TG.Year , 1, "(das )?(EOY|jahr(es)? ?ende|ende (des )?jahr(es)?)" ) ] ruleDaysOfWeek :: [Rule] ruleDaysOfWeek = mkRuleDaysOfWeek [ ( "Montag" , "montags?|mo\\.?" ) , ( "Dienstag" , "die?nstags?|di\\.?" ) , ( "Mittwoch" , "mittwochs?|mi\\.?" ) , ( "Donnerstag", "donn?erstag|do\\.?" ) , ( "Freitag" , "freitags?|fr\\.?" ) , ( "Samstag" , "samstags?|sonnabends?|sa\\.?" ) , ( "Sonntag" , "sonntags?|so\\.?" ) ] ruleMonths :: [Rule] ruleMonths = mkRuleMonths [ ( "Januar" , "januar|jan\\.?" ) , ( "Februar" , "februar|feb\\.?" ) , ( "Marz" , "m(ä)rz|m(ä)r\\.?" ) , ( "April" , "april|apr\\.?" ) , ( "Mai" , "mai\\.?" ) , ( "Juni" , "juni|jun\\.?" ) , ( "Juli" , "juli|jul\\.?" ) , ( "August" , "august|aug\\.?" ) , ( "September", "september|sept?\\.?" ) , ( "Oktober" , "oktober|okt\\.?" ) , ( "November" , "november|nov\\.?" ) , ( "Dezember" , "dezember|dez\\.?" ) ] ruleSeasons :: [Rule] ruleSeasons = mkRuleSeasons [ ( "sommer" , "sommer" , monthDay 6 21, monthDay 9 23 ) , ( "herbst" , "herbst" , monthDay 9 23, monthDay 12 21 ) , ( "winter" , "winter" , monthDay 12 21, monthDay 3 20 ) , ( "fruhling", "fr(ü)h(ling|jahr)", monthDay 3 20, monthDay 6 21 ) ] ruleHolidays :: [Rule] ruleHolidays = mkRuleHolidays [ ( "Neujahr" , "neujahr(s?tag)?" , monthDay 1 1 ) , ( "Valentinstag" , "valentin'?stag" , monthDay 2 14 ) , ( "Schweizer Bundesfeiertag" , "schweiz(er)? (bundes)?feiertag|bundes feiertag" , monthDay 8 1 ) , ( "Tag der Deutschen Einheit" , "tag (der)? deutsc?hen? einheit" , monthDay 10 3 ) , ( "Oesterreichischer Nationalfeiertag" , "((ö)sterreichischer?)? nationalfeiertag|national feiertag" , monthDay 10 26 ) , ( "Halloween" , "hall?owe?en?" , monthDay 10 31 ) , ( "Allerheiligen" , "allerheiligen?|aller heiligen?" , monthDay 11 1 ) , ( "Nikolaus" , "nikolaus(tag)?|nikolaus tag|nikolo" , monthDay 12 6 ) , ( "Heiligabend" , "heilig(er)? abend" , monthDay 12 24 ) , ( "Weihnachten" , "weih?nacht(en|stag)?" , monthDay 12 25 ) , ( "Silvester" , "silvester" , monthDay 12 31 ) , ( "Muttertag" , "mutt?ertag|mutt?er (tag)?" , nthDOWOfMonth 2 7 5 ) , ( "Vatertag" , "vatt?er( ?tag)?" , nthDOWOfMonth 3 7 6 ) ] ruleRelativeMinutesTotillbeforeIntegerHourofday :: Rule ruleRelativeMinutesTotillbeforeIntegerHourofday = Rule { name = "relative minutes to|till|before (hour-of-day)" , pattern = [ Predicate $ isIntegerBetween 1 59 , regex "vor" , Predicate isAnHourOfDay ] , prod = \tokens -> case tokens of (token:_:Token Time td:_) -> do n <- getIntValue token t <- minutesBefore n td Just $ Token Time t _ -> Nothing } ruleQuarterTotillbeforeIntegerHourofday :: Rule ruleQuarterTotillbeforeIntegerHourofday = Rule { name = "quarter to|till|before (hour-of-day)" , pattern = [regex "vie?rtel vor" , Predicate isAnHourOfDay ] , prod = \tokens -> case tokens of (_:Token Time td:_) -> do t <- minutesBefore 15 td Just $ Token Time t _ -> Nothing } ruleHalfTotillbeforeIntegerHourofday :: Rule ruleHalfTotillbeforeIntegerHourofday = Rule { name = "half to|till|before (hour-of-day)" , pattern = [ regex "halbe? vor" , Predicate isAnHourOfDay ] , prod = \tokens -> case tokens of (_:Token Time td:_) -> do t <- minutesBefore 30 td Just $ Token Time t _ -> Nothing } ruleTheOrdinalCycleOfTime :: Rule ruleTheOrdinalCycleOfTime = Rule { name = "the of