-- 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.KO.Rules ( rules ) where import Prelude import qualified Data.Text as Text import Duckling.Dimensions.Types import Duckling.Duration.Helpers (isGrain) 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 ruleHolidays :: [Rule] ruleHolidays = mkRuleHolidays [ ( "Liberation Day" , "광복절" , monthDay 8 15 ) , ( "Constitution Day" , "제헌절" , monthDay 7 17 ) , ( "New Year's Day" , "(신정)|(설날)" , monthDay 1 1 ) , ( "Hangul Day" , "한글날" , monthDay 10 9 ) , ( "National Foundation Day" , "개천절" , monthDay 10 3 ) , ( "Independence Movement Day" , "삼일절" , monthDay 3 1 ) , ( "Memorial Day" , "현충일" , monthDay 6 6 ) , ( "Christmas" , "크리스마스" , monthDay 12 25 ) , ( "Christmas Eve" , "(크리스마스)?이브" , monthDay 12 24 ) , ( "Children's Day" , "어린이날" , monthDay 5 5 ) ] ruleSeasons :: [Rule] ruleSeasons = mkRuleSeasons [ ( "Summer" , "여름" , monthDay 6 21, monthDay 9 23 ) , ( "Fall" , "가을" , monthDay 9 23, monthDay 12 21 ) , ( "Winter" , "겨울" , monthDay 12 21, monthDay 3 20 ) , ( "Spring" , "봄" , monthDay 3 20, monthDay 6 21 ) ] ruleDaysOfWeek :: [Rule] ruleDaysOfWeek = mkRuleDaysOfWeek [ ( "Monday" , "월(요일|욜)" ) , ( "Tuesday" , "화(요일|욜)" ) , ( "Wednesday" , "수(요일|욜)" ) , ( "Thursday" , "목(요일|욜)" ) , ( "Friday" , "금(요일|욜)" ) , ( "Saturday" , "토(요일|욜)" ) , ( "Sunday" , "일(요일|욜)" ) ] ruleNamedday :: Rule ruleNamedday = Rule { name = "에" , pattern = [ Predicate isADayOfWeek , regex "에" ] , prod = \tokens -> case tokens of (x:_) -> Just x _ -> Nothing } ruleTheDayAfterTomorrow :: Rule ruleTheDayAfterTomorrow = Rule { name = "the day after tomorrow - 내일모레" , pattern = [ regex "(내일)?모\xb808" ] , prod = \_ -> tt . cycleNthAfter False TG.Day 1 $ cycleNth TG.Day 1 } ruleTimeofday4 :: Rule ruleTimeofday4 = Rule { name = "이전" , pattern = [ Predicate isATimeOfDay , regex "(이)?전" ] , prod = \tokens -> case tokens of (Token Time td:_) -> tt $ withDirection TTime.Before td _ -> Nothing } ruleDay :: Rule ruleDay = Rule { name = "day" , pattern = [ Predicate isDOMInteger , regex "일" ] , prod = \tokens -> case tokens of (token:_) -> do v <- getIntValue token tt $ dayOfMonth v _ -> Nothing } ruleSinceTimeofday :: Rule ruleSinceTimeofday = Rule { name = "since " , pattern = [ Predicate isATimeOfDay , regex "이래로" ] , prod = \tokens -> case tokens of (Token Time td:_) -> tt . withDirection TTime.After $ predNth (- 1) False td _ -> Nothing } ruleThisDayofweek :: Rule ruleThisDayofweek = Rule { name = "this " , pattern = [ regex "이번(주)?|금주" , Predicate isADayOfWeek ] , prod = \tokens -> case tokens of (_:Token Time td:_) -> tt $ predNth 0 False td _ -> Nothing } ruleLastTime :: Rule ruleLastTime = Rule { name = "last