diff --git a/.gitignore b/.gitignore index 676b4c7..ab9c6dd 100644 --- a/.gitignore +++ b/.gitignore @@ -11,3 +11,5 @@ stack-hie.yaml* .vscode/ result *.txt +stack-hie.yaml +stack-hie.yaml.lock diff --git a/package.yaml b/package.yaml index 676b8e9..2538c35 100644 --- a/package.yaml +++ b/package.yaml @@ -110,6 +110,7 @@ tests: - tasty-hspec - tasty-hunit - tasty-quickcheck + - text - time - tztime - QuickCheck diff --git a/src/TzBot/BotMain.hs b/src/TzBot/BotMain.hs index 623dc19..d865344 100644 --- a/src/TzBot/BotMain.hs +++ b/src/TzBot/BotMain.hs @@ -92,8 +92,12 @@ run opts = do managed $ withTzCacheDefault defaultMessageInfoCachingTime bsReportEntries <- managed $ withTzCacheDefault cCacheReportDialog - -- auto-acknowledge received messages + + let defaultConversationStateCachingTime = hour 12 + bsConversationStateCache <- + managed $ withTzCacheDefault defaultConversationStateCachingTime (bsLogNamespace, bsLogContext, bsLogEnv) <- managed $ withLogger cLogLevel + -- auto-acknowledge received messages liftIO $ runSocketMode sCfg $ handler gracefulShutdownContainer BotState {..} withFeedbackConfig :: BotConfig -> (FeedbackConfig -> IO a) -> IO a diff --git a/src/TzBot/Parser.hs b/src/TzBot/Parser.hs index 6586e33..6624f73 100644 --- a/src/TzBot/Parser.hs +++ b/src/TzBot/Parser.hs @@ -4,11 +4,14 @@ module TzBot.Parser ( parseTimeRefs + , parseWithEmptyContext ) where import Universum hiding (many, toList, try) +import Control.Lens.Operators import Data.Char (isUpper) +import Data.List qualified as L import Data.Map qualified as M import Data.String.Conversions (cs) import Data.Text qualified as T @@ -18,274 +21,420 @@ import Data.Time.Calendar.Compat (DayOfMonth, MonthOfYear, Year) import Data.Time.LocalTime (TimeOfDay(..)) import Data.Time.Zones.All (TZLabel, tzNameLabelMap) import Glider.NLP.Tokenizer (Token(..), tokenize) -import Text.Megaparsec hiding (Token) +import Text.Interpolation.Nyan (int, rmode') +import Text.Megaparsec hiding (State, Token) import TzBot.Instances () +import TzBot.TimeContext (TimeContext(..), emptyTimeContext, tcCurrentDateRefL, tcCurrentLocRefL) import TzBot.TimeReference import TzBot.Util import TzBot.Util qualified as CI type TzParser = Parsec Void [Token] -{- | Parses time references from an input string. +{- | Parses time references from an input string using provided time context + - and produces a new time context. ->>> parseTimeRefs "let's meet tuesday at 10am" +>>> parseWithEmptyContext "let's meet tuesday at 10am" [TimeReference {trText = "tuesday at 10am", trTimeOfDay = 10:00:00, trDateRef = Just (DayOfWeekRef Tuesday), trLocationRef = Nothing}] ->>> parseTimeRefs "i can do it at 3pm MDT" +>>> parseWithEmptyContext "i can do it at 3pm MDT" [TimeReference {trText = "at 3pm MDT", trTimeOfDay = 15:00:00, trDateRef = Nothing, trLocationRef = Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "MDT", tzaiOffsetMinutes = -360, tzaiFullName = "Mountain Daylight Time (North America)"}))}] ->>> parseTimeRefs "how about between 2pm and 3pm?" +>>> parseWithEmptyContext "how about between 2pm and 3pm?" [TimeReference {trText = "2pm", trTimeOfDay = 14:00:00, trDateRef = Nothing, trLocationRef = Nothing},TimeReference {trText = "3pm", trTimeOfDay = 15:00:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "Does 10am work for you?" +>>> parseWithEmptyContext "Does 10am work for you?" [TimeReference {trText = "10am", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "That doesn't work for me, what about 10:30 AM?" +>>> parseWithEmptyContext "That doesn't work for me, what about 10:30 AM?" [TimeReference {trText = "10:30 AM", trTimeOfDay = 10:30:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "I can only be there at 16:00" +>>> parseWithEmptyContext "I can only be there at 16:00" [TimeReference {trText = "at 16:00", trTimeOfDay = 16:00:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "10am tomorrow" +>>> parseWithEmptyContext "10am tomorrow" [TimeReference {trText = "10am tomorrow", trTimeOfDay = 10:00:00, trDateRef = Just (DaysFromToday 1), trLocationRef = Nothing}] ->>> parseTimeRefs "today at 3pm" +>>> parseWithEmptyContext "today at 3pm" [TimeReference {trText = "today at 3pm", trTimeOfDay = 15:00:00, trDateRef = Just (DaysFromToday 0), trLocationRef = Nothing}] ->>> parseTimeRefs "10am in 2 days" +>>> parseWithEmptyContext "10am in 2 days" [TimeReference {trText = "10am in 2 days", trTimeOfDay = 10:00:00, trDateRef = Just (DaysFromToday 2), trLocationRef = Nothing}] ->>> parseTimeRefs "tuesday at 3pm" +>>> parseWithEmptyContext "tuesday at 3pm" [TimeReference {trText = "tuesday at 3pm", trTimeOfDay = 15:00:00, trDateRef = Just (DayOfWeekRef Tuesday), trLocationRef = Nothing}] ->>> parseTimeRefs "at 3pm on tuesday" +>>> parseWithEmptyContext "at 3pm on tuesday" [TimeReference {trText = "at 3pm on tuesday", trTimeOfDay = 15:00:00, trDateRef = Just (DayOfWeekRef Tuesday), trLocationRef = Nothing}] ->>> parseTimeRefs "at 11am on the 4th " +>>> parseWithEmptyContext "at 11am on the 4th " [TimeReference {trText = "at 11am on the 4th", trTimeOfDay = 11:00:00, trDateRef = Just (DayOfMonthRef 4 Nothing), trLocationRef = Nothing}] ->>> parseTimeRefs "at 11am on the 4th of April" +>>> parseWithEmptyContext "at 11am on the 4th of April" [TimeReference {trText = "at 11am on the 4th of April", trTimeOfDay = 11:00:00, trDateRef = Just (DayOfMonthRef 4 (Just (4,Nothing))), trLocationRef = Nothing}] ->>> parseTimeRefs "at 11am on April 4" +>>> parseWithEmptyContext "at 11am on April 4" [TimeReference {trText = "at 11am on April 4", trTimeOfDay = 11:00:00, trDateRef = Just (DayOfMonthRef 4 (Just (4,Nothing))), trLocationRef = Nothing}] ->>> parseTimeRefs "at 11am on 4 April" +>>> parseWithEmptyContext "at 11am on 4 April" [TimeReference {trText = "at 11am on 4 April", trTimeOfDay = 11:00:00, trDateRef = Just (DayOfMonthRef 4 (Just (4,Nothing))), trLocationRef = Nothing}] ->>> parseTimeRefs "9am in europe/london" +>>> parseWithEmptyContext "9am in europe/london" [TimeReference {trText = "9am in europe/london", trTimeOfDay = 09:00:00, trDateRef = Nothing, trLocationRef = Just (TimeZoneRef Europe__London)}] ->>> parseTimeRefs "2pm CST" +>>> parseWithEmptyContext "2pm CST" [TimeReference {trText = "2pm CST", trTimeOfDay = 14:00:00, trDateRef = Nothing, trLocationRef = Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "CST", tzaiOffsetMinutes = -360, tzaiFullName = "Central Standard Time (North America)"}))}] ->>> parseTimeRefs "10am UTC+03:00" +>>> parseWithEmptyContext "10am UTC+03:00" [TimeReference {trText = "10am UTC+03:00", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Just (OffsetRef 180)}] ->>> parseTimeRefs "10am UTC+3" +>>> parseWithEmptyContext "10am UTC+3" [TimeReference {trText = "10am UTC+3", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Just (OffsetRef 180)}] ->>> parseTimeRefs "10am UTC +3" +>>> parseWithEmptyContext "10am UTC +3" [TimeReference {trText = "10am UTC +3", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Just (OffsetRef 180)}] ->>> parseTimeRefs "10am UTC-3" +>>> parseWithEmptyContext "10am UTC-3" [TimeReference {trText = "10am UTC-3", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Just (OffsetRef (-180))}] ->>> parseTimeRefs "10am UTC -3" +>>> parseWithEmptyContext "10am UTC -3" [TimeReference {trText = "10am UTC -3", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Just (OffsetRef (-180))}] ->>> parseTimeRefs "10am UTC-blabla" +>>> parseWithEmptyContext "10am UTC-blabla" [TimeReference {trText = "10am", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "Let's meet between 10am and 11:30am" +>>> parseWithEmptyContext "Let's meet between 10am and 11:30am" [TimeReference {trText = "10am", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Nothing},TimeReference {trText = "11:30am", trTimeOfDay = 11:30:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "35pm" +>>> parseWithEmptyContext "35pm" [] ->>> parseTimeRefs "35pmkek" +>>> parseWithEmptyContext "35pmkek" [] ->>> parseTimeRefs "15:00pm" +>>> parseWithEmptyContext "15:00pm" [TimeReference {trText = "15:00pm", trTimeOfDay = 15:00:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "13:00 Nov 06" +>>> parseWithEmptyContext "13:00 Nov 06" [TimeReference {trText = "13:00 Nov 06", trTimeOfDay = 13:00:00, trDateRef = Just (DayOfMonthRef 6 (Just (11,Nothing))), trLocationRef = Nothing}] ->>> parseTimeRefs "11:12:13 nOv 1" +>>> parseWithEmptyContext "11:12:13 nOv 1" [TimeReference {trText = "11:12:13 nOv 1", trTimeOfDay = 11:12:00, trDateRef = Just (DayOfMonthRef 1 (Just (11,Nothing))), trLocationRef = Nothing}] ->>> parseTimeRefs "13:00 06 Nov" +>>> parseWithEmptyContext "13:00 06 Nov" [TimeReference {trText = "13:00 06 Nov", trTimeOfDay = 13:00:00, trDateRef = Just (DayOfMonthRef 6 (Just (11,Nothing))), trLocationRef = Nothing}] ->>> parseTimeRefs "10am 11am" +>>> parseWithEmptyContext "10am 11am" [TimeReference {trText = "10am", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Nothing},TimeReference {trText = "11am", trTimeOfDay = 11:00:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "1:12:23pm" +>>> parseWithEmptyContext "1:12:23pm" [TimeReference {trText = "1:12:23pm", trTimeOfDay = 13:12:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "12am the day after tomorrow" +>>> parseWithEmptyContext "12am the day after tomorrow" [TimeReference {trText = "12am the day after tomorrow", trTimeOfDay = 12:00:00, trDateRef = Just (DaysFromToday 2), trLocationRef = Nothing}] ->>> parseTimeRefs "12am day after tomorrow" +>>> parseWithEmptyContext "12am day after tomorrow" [TimeReference {trText = "12am day after tomorrow", trTimeOfDay = 12:00:00, trDateRef = Just (DaysFromToday 2), trLocationRef = Nothing}] ->>> parseTimeRefs "12am 3 days ahead" +>>> parseWithEmptyContext "12am 3 days ahead" [TimeReference {trText = "12am 3 days ahead", trTimeOfDay = 12:00:00, trDateRef = Just (DaysFromToday 3), trLocationRef = Nothing}] ->>> parseTimeRefs "9:3am" +>>> parseWithEmptyContext "9:3am" [] ->>> parseTimeRefs "13:00 06 nov" +>>> parseWithEmptyContext "13:00 06 nov" [TimeReference {trText = "13:00 06 nov", trTimeOfDay = 13:00:00, trDateRef = Just (DayOfMonthRef 6 (Just (11,Nothing))), trLocationRef = Nothing}] ->>> parseTimeRefs "13:00 nov 06" +>>> parseWithEmptyContext "13:00 nov 06" [TimeReference {trText = "13:00 nov 06", trTimeOfDay = 13:00:00, trDateRef = Just (DayOfMonthRef 6 (Just (11,Nothing))), trLocationRef = Nothing}] ->>> parseTimeRefs "today,10am" +>>> parseWithEmptyContext "today,10am" [TimeReference {trText = "today,10am", trTimeOfDay = 10:00:00, trDateRef = Just (DaysFromToday 0), trLocationRef = Nothing}] ->>> parseTimeRefs "today , 10am" +>>> parseWithEmptyContext "today , 10am" [TimeReference {trText = "today , 10am", trTimeOfDay = 10:00:00, trDateRef = Just (DaysFromToday 0), trLocationRef = Nothing}] ->>> parseTimeRefs "today, 10am" +>>> parseWithEmptyContext "today, 10am" [TimeReference {trText = "today, 10am", trTimeOfDay = 10:00:00, trDateRef = Just (DaysFromToday 0), trLocationRef = Nothing}] ->>> parseTimeRefs "today ,10am" +>>> parseWithEmptyContext "today ,10am" [TimeReference {trText = "today ,10am", trTimeOfDay = 10:00:00, trDateRef = Just (DaysFromToday 0), trLocationRef = Nothing}] ->>> parseTimeRefs "10am aMeRiCa/Argentina/Buenos_Aires" +>>> parseWithEmptyContext "10am aMeRiCa/Argentina/Buenos_Aires" [TimeReference {trText = "10am aMeRiCa/Argentina/Buenos_Aires", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Just (TimeZoneRef America__Argentina__Buenos_Aires)}] ->>> parseTimeRefs "10am America/North_Dakota/New_Salem" +>>> parseWithEmptyContext "10am America/North_Dakota/New_Salem" [TimeReference {trText = "10am America/North_Dakota/New_Salem", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Just (TimeZoneRef America__North_Dakota__New_Salem)}] ->>> parseTimeRefs "10am America/port-au-Prince" +>>> parseWithEmptyContext "10am America/port-au-Prince" [TimeReference {trText = "10am America/port-au-Prince", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Just (TimeZoneRef America__Port_au_Prince)}] ->>> parseTimeRefs "10am MSKC" +>>> parseWithEmptyContext "10am MSKC" [TimeReference {trText = "10am MSKC", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Just (UnknownTimeZoneAbbreviationRef (UnknownTimeZoneAbbrev {utzaAbbrev = "MSKC", utzaCandidates = ["MSK"]}))}] ->>> parseTimeRefs "10am KSMC" +>>> parseWithEmptyContext "10am KSMC" [TimeReference {trText = "10am KSMC", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Just (UnknownTimeZoneAbbreviationRef (UnknownTimeZoneAbbrev {utzaAbbrev = "KSMC", utzaCandidates = []}))}] ->>> parseTimeRefs "10am KSMc" +>>> parseWithEmptyContext "10am KSMc" [TimeReference {trText = "10am", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "10am K" +>>> parseWithEmptyContext "10am K" [TimeReference {trText = "10am", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "10am KAMAZN" +>>> parseWithEmptyContext "10am KAMAZN" [TimeReference {trText = "10am", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "01:03 6 November America/Winnipeg" +>>> parseWithEmptyContext "01:03 6 November America/Winnipeg" [TimeReference {trText = "01:03 6 November America/Winnipeg", trTimeOfDay = 01:03:00, trDateRef = Just (DayOfMonthRef 6 (Just (11,Nothing))), trLocationRef = Just (TimeZoneRef America__Winnipeg)}] ->>> parseTimeRefs "01:03 6 November 2022 America/Winnipeg" +>>> parseWithEmptyContext "01:03 6 November 2022 America/Winnipeg" [TimeReference {trText = "01:03 6 November 2022 America/Winnipeg", trTimeOfDay = 01:03:00, trDateRef = Just (DayOfMonthRef 6 (Just (11,Just 2022))), trLocationRef = Just (TimeZoneRef America__Winnipeg)}] ->>> parseTimeRefs "01:03 2022 6 November America/Winnipeg" +>>> parseWithEmptyContext "01:03 2022 6 November America/Winnipeg" [TimeReference {trText = "01:03 2022 6 November America/Winnipeg", trTimeOfDay = 01:03:00, trDateRef = Just (DayOfMonthRef 6 (Just (11,Just 2022))), trLocationRef = Just (TimeZoneRef America__Winnipeg)}] ->>> parseTimeRefs "7.30 pm " +>>> parseWithEmptyContext "7.30 pm " [TimeReference {trText = "7.30 pm", trTimeOfDay = 19:30:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "7.30" +>>> parseWithEmptyContext "7.30" [] ->>> parseTimeRefs "19h " +>>> parseWithEmptyContext "19h " [TimeReference {trText = "19h", trTimeOfDay = 19:00:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "19h01 " +>>> parseWithEmptyContext "19h01 " [TimeReference {trText = "19h01", trTimeOfDay = 19:01:00, trDateRef = Nothing, trLocationRef = Nothing}] ->>> parseTimeRefs "7:30pm 03/08/2022" +>>> parseWithEmptyContext "7:30pm 03/08/2022" [TimeReference {trText = "7:30pm 03/08/2022", trTimeOfDay = 19:30:00, trDateRef = Just (DayOfMonthRef 3 (Just (8,Just 2022))), trLocationRef = Nothing}] ->>> parseTimeRefs "7:30pm 3-08-2022" +>>> parseWithEmptyContext "7:30pm 3-08-2022" [TimeReference {trText = "7:30pm 3-08-2022", trTimeOfDay = 19:30:00, trDateRef = Just (DayOfMonthRef 3 (Just (8,Just 2022))), trLocationRef = Nothing}] ->>> parseTimeRefs "7:30pm 3.08.2022" +>>> parseWithEmptyContext "7:30pm 3.08.2022" [TimeReference {trText = "7:30pm 3.08.2022", trTimeOfDay = 19:30:00, trDateRef = Just (DayOfMonthRef 3 (Just (8,Just 2022))), trLocationRef = Nothing}] ->>> parseTimeRefs "7:30pm 2022/08/3" +>>> parseWithEmptyContext "7:30pm 2022/08/3" [TimeReference {trText = "7:30pm 2022/08/3", trTimeOfDay = 19:30:00, trDateRef = Just (DayOfMonthRef 3 (Just (8,Just 2022))), trLocationRef = Nothing}] ->>> parseTimeRefs "2022.8.03 7:30 pm " +>>> parseWithEmptyContext "2022.8.03 7:30 pm " [TimeReference {trText = "2022.8.03 7:30 pm", trTimeOfDay = 19:30:00, trDateRef = Just (DayOfMonthRef 3 (Just (8,Just 2022))), trLocationRef = Nothing}] ->>> parseTimeRefs "7:30pm 2022.8.03 America/Havana" +>>> parseWithEmptyContext "7:30pm 2022.8.03 America/Havana" [TimeReference {trText = "7:30pm 2022.8.03 America/Havana", trTimeOfDay = 19:30:00, trDateRef = Just (DayOfMonthRef 3 (Just (8,Just 2022))), trLocationRef = Just (TimeZoneRef America__Havana)}] +>>> parseWithEmptyContext "tomorrow 10am -11 am" +[TimeReference {trText = "tomorrow 10am", trTimeOfDay = 10:00:00, trDateRef = Just (DaysFromToday 1), trLocationRef = Nothing},TimeReference {trText = "tomorrow 11 am", trTimeOfDay = 11:00:00, trDateRef = Just (DaysFromToday 1), trLocationRef = Nothing}] + +>>> parseWithEmptyContext "tomorrow 10am / 11 am" +[TimeReference {trText = "tomorrow 10am", trTimeOfDay = 10:00:00, trDateRef = Just (DaysFromToday 1), trLocationRef = Nothing},TimeReference {trText = "tomorrow 11 am", trTimeOfDay = 11:00:00, trDateRef = Just (DaysFromToday 1), trLocationRef = Nothing}] + +>>> parseWithEmptyContext "between 10am and 11:30am UTC" +[TimeReference {trText = "10am UTC", trTimeOfDay = 10:00:00, trDateRef = Nothing, trLocationRef = Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))},TimeReference {trText = "11:30am UTC", trTimeOfDay = 11:30:00, trDateRef = Nothing, trLocationRef = Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))}] + +>>> parseWithEmptyContext "Let's go on Wednesday at 10:00 or 11:00." +[TimeReference {trText = "on Wednesday at 10:00", trTimeOfDay = 10:00:00, trDateRef = Just (DayOfWeekRef Wednesday), trLocationRef = Nothing},TimeReference {trText = "on Wednesday 11:00", trTimeOfDay = 11:00:00, trDateRef = Just (DayOfWeekRef Wednesday), trLocationRef = Nothing}] + +>>> parseWithEmptyContext "10-11pm tomorrow works for me" +[TimeReference {trText = "10pm tomorrow", trTimeOfDay = 22:00:00, trDateRef = Just (DaysFromToday 1), trLocationRef = Nothing},TimeReference {trText = "11pm tomorrow", trTimeOfDay = 23:00:00, trDateRef = Just (DaysFromToday 1), trLocationRef = Nothing}] + +>>> parseWithEmptyContext "How about 10:00 or 11:00 pm tomorrow?" +[TimeReference {trText = "10:00 pm tomorrow", trTimeOfDay = 22:00:00, trDateRef = Just (DaysFromToday 1), trLocationRef = Nothing},TimeReference {trText = "11:00 pm tomorrow", trTimeOfDay = 23:00:00, trDateRef = Just (DaysFromToday 1), trLocationRef = Nothing}] + +>>> parseWithEmptyContext "7.30-8.30pm" +[TimeReference {trText = "7.30pm", trTimeOfDay = 19:30:00, trDateRef = Nothing, trLocationRef = Nothing},TimeReference {trText = "8.30pm", trTimeOfDay = 20:30:00, trDateRef = Nothing, trLocationRef = Nothing}] + +>>> parseWithEmptyContext "7.30am-8.30pm tomorrow" +[TimeReference {trText = "7.30am tomorrow", trTimeOfDay = 07:30:00, trDateRef = Just (DaysFromToday 1), trLocationRef = Nothing},TimeReference {trText = "8.30pm tomorrow", trTimeOfDay = 20:30:00, trDateRef = Just (DaysFromToday 1), trLocationRef = Nothing}] + +>>> parseWithEmptyContext "7.30-8.30" +[] + -} -parseTimeRefs :: Text -> [TimeReference] +parseTimeRefs :: Text -> State TimeContext [TimeReference] parseTimeRefs = -- TODO use better error handling - fromMaybe [] + fmap (map matchedToPlain) + . applyContexts + . fromMaybe [] . parseMaybe timeRefsParser -- time reference can be either at the beginning or after a space . (Whitespace :) . tokenize --- | Parser for multiple 'TimeReference' s. --- --- This looks for all of them in the input and ignores everything surrounding. -timeRefsParser :: TzParser [TimeReference] +-- | Parse given text using provided time context and produce new time context. +parseWithEmptyContext :: Text -> [TimeReference] +parseWithEmptyContext = flip evalState emptyTimeContext . parseTimeRefs + +applyContexts :: [ApplyContextToken] -> State TimeContext [TimeReferenceMatched] +applyContexts lst = mapMaybe getTimeRef <$> mapM processACTToken lst + where + getTimeRef (ACTTimeReference t) = Just t + getTimeRef _ = Nothing + + processACTToken :: ApplyContextToken -> State TimeContext ApplyContextToken + processACTToken = \case + d@(ACTDateReference ma) -> do + setCurrentDate ma + pure d + ACTTimeReference tr -> do + tr' <- useCurrentDate tr >>= useCurrentLoc + pure $ ACTTimeReference tr' + where + setCurrentDate :: Matched DateReference -> State TimeContext () + setCurrentDate ref = tcCurrentDateRefL .= Just ref + + useCurrentDate :: TimeReferenceMatched -> State TimeContext TimeReferenceMatched + useCurrentDate tr = case trDateRef tr of + Nothing -> do + mbDefaultCurDate <- tcCurrentDateRef <$> get + pure $ flip (whenJustFunc mbDefaultCurDate) tr \defaultCurDate t -> + addDateIfMissing defaultCurDate t + Just dr -> do + setCurrentDate dr + pure tr + + setCurrentLoc :: Matched LocationReference -> State TimeContext () + setCurrentLoc ref = tcCurrentLocRefL .= Just ref + + useCurrentLoc :: TimeReferenceMatched -> State TimeContext TimeReferenceMatched + useCurrentLoc tr = case trLocationRef tr of + Nothing -> do + mbDefaultCurLoc <- tcCurrentLocRef <$> get + pure $ flip (whenJustFunc mbDefaultCurLoc) tr \defaultCurLoc t -> + addLocationIfMissing defaultCurLoc t + Just lr -> do + setCurrentLoc lr + pure tr + +-- | Parser for a list whose element is either a full time reference or a date reference. +timeRefsParser :: TzParser [ApplyContextToken] timeRefsParser = choice' [ do - tr <- try timeRefParser + tr <- try applyContextTokenParser trs <- timeRefsParser - return $ tr : trs + return $ tr <> trs , anySingle >> timeRefsParser , takeRest >> pure [] ] --- | Parses a single 'TimeReference', consuming all input. -timeRefParser :: TzParser TimeReference +data ApplyContextToken + = ACTTimeReference TimeReferenceMatched + | ACTDateReference (Matched DateReference) + deriving stock (Show, Eq, Generic) + +-- | Either time reference or date reference +applyContextTokenParser :: TzParser [ApplyContextToken] +applyContextTokenParser = choice' + [ map ACTTimeReference <$> timeRefConjugParser + , L.singleton . ACTDateReference . matched <$> match dateRefParser + ] + +-- | Parses entries like @between 10am and 11am@ or +-- @10am-11am on thursday or 1pm-2pm on wednesday@ +timeRefConjugParser :: TzParser [TimeReferenceMatched] +timeRefConjugParser = do + firstConjugComponent <- timeRefParser + let conjugParser conjWord = do + optional' space + _ <- word' conjWord + -- no space here before `timeRefParser` requires a space before the contents + secondConjugComponent <- timeRefParser + pure $ unifyConjugComponents $ firstConjugComponent <> secondConjugComponent + + unifyConjugComponents :: [TimeReferenceMatched] -> [TimeReferenceMatched] + unifyConjugComponents lst = do + let getUnique :: Eq a => (TimeReferenceMatched -> Maybe a) -> Maybe a + getUnique getter = do + let many = L.nub $ mapMaybe getter lst + case many of + [item] -> Just item + _ -> Nothing + let locRef = getUnique trLocationRef + dateRef = getUnique trDateRef + -- TODO: use lenses + flip map lst $ + (whenJustFunc locRef \l tr -> addLocationIfMissing l tr) + . whenJustFunc dateRef \d tr -> addDateIfMissing d tr + + choice' + -- note that and/or can be parsed either as conjugations or as "hyphens", + -- in the second case am/pm context is also shared + [ conjugParser "and" + , conjugParser "or" + , pure firstConjugComponent + ] + +addLocationIfMissing + :: Matched LocationReference + -> TimeReferenceMatched + -> TimeReferenceMatched +addLocationIfMissing l tr = + if isNothing (trLocationRef tr) + then tr { trLocationRef = Just l, trText = [int||#{trText tr} (#{mtText l})|] } + else tr + +addDateIfMissing + :: Matched DateReference + -> TimeReferenceMatched + -> TimeReferenceMatched +addDateIfMissing d tr = + if isNothing (trDateRef tr) + then tr { trDateRef = Just d, trText = [int||#{trText tr} (#{mtText d})|] } + else tr + +-- | Parses coupled 'TimeReference's, collecting the source text. +timeRefParser :: TzParser [TimeReferenceMatched] timeRefParser = do _ <- space - (newTrText, timeReference) <- match timeRefParser' - return timeReference { trText = concatTokens newTrText } - --- | Parses a single 'TimeReference', but does not collect the source text. -timeRefParser' :: TzParser TimeReference -timeRefParser' = do - let trText = "" - precBuilder <- fromMaybe builderInit <$> do + (precText, precBuilder) <- match $ fromMaybe builderInit <$> do res <- optional' (builderParser False builderInit) optional' spacedComma pure res - trTimeOfDay <- timeOfDayParser - builder <- fromMaybe builderInit <$> optional' (builderParser True precBuilder) + timeEntry <- timeEntryParser + (afterText, builder) <- match $ fromMaybe builderInit <$> optional' (builderParser True precBuilder) let trLocationRef = trbLocRef builder trDateRef = trbDateRef builder - pure TimeReference {..} + let mkTrText refText = + T.concat [concatTokens precText, refText, concatTokens afterText] + let mkTimeReference todWithText = TimeReference + { trText = mkTrText $ mtText todWithText + , trTimeOfDay = mtValue todWithText + , trDateRef + , trLocationRef + } + pure $ map mkTimeReference case timeEntry of + TESingle todwt -> [todwt] + TEPair todwt todwt' -> [todwt, todwt'] ---------------------------------------------------------------------------- ---- Collecting of optional time contexts ---------------------------------------------------------------------------- data ContextBuilder = ContextBuilder - { trbDateRef :: Maybe DateReference - , trbLocRef :: Maybe LocationReference + { trbDateRef :: Maybe (Matched DateReference) + , trbLocRef :: Maybe (Matched LocationReference) } deriving stock (Show, Eq) builderInit :: ContextBuilder builderInit = ContextBuilder Nothing Nothing data SumContextBuilder - = SCBDate DateReference - | SCBLocRef LocationReference + = SCBDate (Matched DateReference) + | SCBLocRef (Matched LocationReference) sumBuilderParser :: TzParser SumContextBuilder sumBuilderParser = - choice' [SCBDate <$> dateRefParser, SCBLocRef <$> locRefParser] + choice' + [ SCBDate . matched <$> match dateRefParser + , SCBLocRef . matched <$> match locRefParser + ] builderParser :: Bool -> ContextBuilder -> TzParser ContextBuilder builderParser allowSpace b = do sumB <- optional' - (when allowSpace (void $ optional' spacedComma) >> sumBuilderParser) - case sumB of + (when allowSpace (void $ optional' spacedComma) >> matched <$> match sumBuilderParser) + case fmap mtValue sumB of Just (SCBDate dr) -> do when (isJust $ trbDateRef b) empty builderParser True b { trbDateRef = Just dr } @@ -295,11 +444,66 @@ builderParser allowSpace b = do Nothing -> pure b ---------------------------------------------------------------------------- --- | Parses a 'TimeOfDay'. --- --- This is permissive in the space, as it allows none to be between the time and --- the AM/PM. -timeOfDayParser :: TzParser TimeOfDay +matched :: ([Token], a) -> Matched a +matched (ts, val) = Matched (concatTokens ts) val + +data TimeEntry + = TESingle (Matched TimeOfDay) + -- ^ E.g. @10am@ + | TEPair (Matched TimeOfDay) (Matched TimeOfDay) + -- ^ E.g. @10am-11am@ + +-- | Parses either a single time of day or a pair with shared +-- date, location and am/pm contexts. +timeEntryParser :: TzParser TimeEntry +timeEntryParser = do + let todWithTextParser = matched <$> match timeOfDayParser + firstRef <- todWithTextParser + let delimitedPair :: TzParser a -> TzParser TimeEntry + delimitedPair delim = do + optional' space + delim + optional' space + secondRef <- todWithTextParser + let getIsAm + :: Matched (Maybe (TimeOfDay, Maybe $ Matched Bool), Bool -> TimeOfDay) + -> Maybe (Matched Bool) + getIsAm ref = fst (mtValue ref) >>= snd + let isAmOptions = mapMaybe getIsAm [firstRef, secondRef] + let applyIsAm + :: Matched Bool + -> Matched (Maybe (TimeOfDay, Maybe $ Matched Bool), Bool -> TimeOfDay) + -> Matched TimeOfDay + applyIsAm isAm ref = do + let shouldAppend = isNothing $ getIsAm ref + whenFunc shouldAppend (modifyText (<> mtText isAm)) $ fmap (($ mtValue isAm) . snd) ref + + extractDefaultResult :: Matched (Maybe (TimeOfDay, a), b) -> Maybe (Matched TimeOfDay) + extractDefaultResult ref = traverse (fmap fst . fst) ref + + case isAmOptions of + [isAm] -> pure $ (TEPair `on` applyIsAm isAm) firstRef secondRef + _ -> maybe empty pure $ TEPair <$> extractDefaultResult firstRef <*> extractDefaultResult secondRef + + choice' + [ delimitedPair (punct '-') + , delimitedPair (punct '/') + , delimitedPair (word' "or") + , delimitedPair (word' "and") + , TESingle <$> traverse (\(mbRes, _) -> maybe empty (pure . fst) mbRes) firstRef + ] + +-- | Parses a 'TimeOfDay', returning a template for `timeEntryParser`, which can later +-- provide another am/pm context that we can infer by default. +timeOfDayParser + :: TzParser + (Maybe + (TimeOfDay -- if parsed correctly, this is a value with the default am/pm context applied + , Maybe (Matched Bool) -- if am/pm context parsed, return it here + ) + , Bool -> TimeOfDay -- if it turns out that another am/pm context should be applied, + -- provide construction function for that case + ) timeOfDayParser = do _ <- optional' (relationPreposition >> space) hour <- hourParser @@ -328,19 +532,24 @@ timeOfDayParser = do , pure (Nothing, True) ] - isAm <- if isAmRequired - then isAmParser - else fromMaybe True <$> optional' isAmParser - - let todSec = 0 - todHour - | isAm = hour - -- pm here - | hour < 12 = hour + 12 - -- ignore pm if hour > 12 - | otherwise = hour - todMin = fromMaybe 0 maybeMin - pure TimeOfDay {..} + let mkTime isAm = do + let todSec = 0 + todHour + | isAm = hour + -- pm here + | hour < 12 = hour + 12 + -- ignore pm if hour > 12 + | otherwise = hour + todMin = fromMaybe 0 maybeMin + TimeOfDay {..} + + mbIsAm <- optional' $ matched <$> match isAmParser + pure . (,mkTime) $ case mbIsAm of + Just isAm -> Just (mkTime $ mtValue isAm, Just isAm) + Nothing -> + if isAmRequired + then Nothing + else Just (mkTime True, Nothing) isAmParser :: TzParser Bool isAmParser = optional' space >> @@ -395,7 +604,7 @@ dateParserFormat = do y <- yearParser m <- delim >> monthOfYearNumberParser (d, _) <- delim >> dayOfMonthParser - pure $ DayOfMonthRef d $ Just (m, (Just y)) + pure $ DayOfMonthRef d $ Just (m, Just y) format2 :: TzParser a -> TzParser DateReference format2 delim = do @@ -410,7 +619,7 @@ dateParserVerbose :: TzParser DateReference dateParserVerbose = do precYear <- optional' ( do y <- yearParser; spacedComma; pure y ) _ <- optional' (relationPreposition >> space) - (dayOfMonth, monthOfYear) <- choice' $ + (dayOfMonth, monthOfYear) <- choice' [ do _ <- optional' (word' "the" >> space) (dayOfMonth, hasSuffix) <- dayOfMonthParser @@ -517,8 +726,7 @@ isPossibleTimezoneAbbrev w = T.all isUpper w && T.length w >= 2 && T.length w <= 5 - && w /= "AM" - && w /= "PM" + && notElem w ["AM", "PM", "OR", "AND"] -------------------------------------------------------------------------------- -- Storages diff --git a/src/TzBot/ProcessEvents/Common.hs b/src/TzBot/ProcessEvents/Common.hs index a93eee1..8c25c18 100644 --- a/src/TzBot/ProcessEvents/Common.hs +++ b/src/TzBot/ProcessEvents/Common.hs @@ -4,7 +4,7 @@ module TzBot.ProcessEvents.Common ( openModalCommon - , getTimeReferencesFromMessage + , getTimeReferencesAndNewStateFromMessage -- * exported for tests , ignoreCodeBlocksManually @@ -18,15 +18,17 @@ import Data.Text qualified as T import Fmt (listF) import Text.Interpolation.Nyan (int, rmode') +import TzBot.Cache qualified as Cache import TzBot.Feedback.Dialog (insertDialogEntry) import TzBot.Feedback.Dialog.Types import TzBot.Logger import TzBot.Parser (parseTimeRefs) import TzBot.Render (TranslationPairs, asForModalM, renderAllTP, renderTemplate) -import TzBot.Slack (BotM, getUserCached, startModal) +import TzBot.Slack (BotM, BotState(bsMessageCache), getUserCached, startModal) import TzBot.Slack.API import TzBot.Slack.API.MessageBlock (UnknownBlockElementLevel2Error(ubeType), extractPieces, splitExtractErrors) +import TzBot.TimeContext import TzBot.TimeReference (TimeReference) import TzBot.Util (WithUnknown(unUnknown)) @@ -45,7 +47,9 @@ openModalCommon openModalCommon message channelId whoTriggeredId triggerId mkModalFunc = do let msgText = mText message msgTimestamp = mTs message - mbTimeRefs <- nonEmpty <$> getTimeReferencesFromMessage message + mbTimeRefs <- fmap (nonEmpty . fst) $ + asks bsMessageCache >>= Cache.fetchWithCache msgId \_ -> + getTimeReferencesAndNewStateFromMessage emptyTimeContext message sender <- getUserCached $ mUser message translationPairs <- fmap join $ forM mbTimeRefs $ \neTimeRefs -> do whoTriggered <- getUserCached whoTriggeredId @@ -66,14 +70,22 @@ openModalCommon message channelId whoTriggeredId triggerId mkModalFunc = do insertDialogEntry guid metadata let modal = mkModalFunc msgText translationPairs guid startModal $ OpenViewReq modal triggerId + where + msgId = mMessageId message -- | Extract separate text pieces from the Slack message that can contain -- the whole time reference and try to find time references inside them. -getTimeReferencesFromMessage - :: Message - -> BotM [TimeReference] -getTimeReferencesFromMessage message = - concatMap parseTimeRefs <$> getTextPiecesFromMessage message +-- Old context (date, timezone, offset, etc.) is used for processing +-- and new one is produced. +getTimeReferencesAndNewStateFromMessage + :: TimeContext + -> Message + -> BotM ([TimeReference], TimeContext) +getTimeReferencesAndNewStateFromMessage oldState message = do + pieces <- getTextPiecesFromMessage message + pure $ + first concat $ + runState (mapM parseTimeRefs pieces) oldState -- | Extract separate text pieces from the Slack message that can contain -- the whole time reference. The main way is analyzing the message's block diff --git a/src/TzBot/ProcessEvents/Message.hs b/src/TzBot/ProcessEvents/Message.hs index 43257ef..c2f1aad 100644 --- a/src/TzBot/ProcessEvents/Message.hs +++ b/src/TzBot/ProcessEvents/Message.hs @@ -19,13 +19,14 @@ import UnliftIO qualified import TzBot.Cache qualified as Cache import TzBot.Config (Config(..)) import TzBot.Logger -import TzBot.ProcessEvents.Common (getTimeReferencesFromMessage) +import TzBot.ProcessEvents.Common import TzBot.Render import TzBot.Slack import TzBot.Slack.API import TzBot.Slack.Events import TzBot.Slack.Fixtures qualified as Fixtures -import TzBot.TimeReference (TimeReference(..)) +import TzBot.TimeContext (emptyTimeContext) +import TzBot.TimeReference (TimeReference) import TzBot.Util (whenT, withMaybe) data MessageEventType = METMessage | METMessageEdited @@ -80,19 +81,16 @@ processMessageEvent evt = katipAddContext (MessageContext msgId) $ whenJustM (filterMessageTypeWithLog evt) $ \mEventType -> whenJustM (withSenderNotBot evt) $ \sender -> do - timeRefs <- getTimeReferencesFromMessage msg - processMessageEvent' evt mEventType sender timeRefs + processMessageEvent' evt mEventType sender where - msg = meMessage evt msgId = mMessageId $ meMessage evt processMessageEvent' :: MessageEvent -> MessageEventType -> User - -> [TimeReference] -> BotM () -processMessageEvent' evt mEventType sender timeRefs = +processMessageEvent' evt mEventType sender = case meChannelType evt of Just CTDirectChannel -> handleDirectMessage _ -> case mEventType of @@ -155,25 +153,52 @@ processMessageEvent' evt mEventType sender timeRefs = } sendEphemeralMessage req + -- threadId is the same as its parent's messageId, + -- so use messageId if there's no thread yet + getMessageThreadId :: ThreadId + getMessageThreadId = fromMaybe (ThreadId $ unMessageId msgId) mbThreadId + handleMessageChanged :: BotM () handleMessageChanged = katipAddNamespaceText "edit" do messageRefsCache <- asks bsMessageCache - mbMessageRefs <- Cache.lookup msgId messageRefsCache + convStateCache <- asks bsConversationStateCache + mbMessageRefsAndState <- Cache.lookup msgId messageRefsCache -- if not found or expired, just ignore this message -- it's too old or just didn't contain any time refs - whenJust mbMessageRefs $ \oldRefs -> do - let newRefsFound = not $ all (`elem` oldRefs) timeRefs + whenJust mbMessageRefsAndState $ \(oldRefs, stateBefore) -> do + (newRefs, stateAfter) <- + getTimeReferencesAndNewStateFromMessage stateBefore msg + mbConversationState <- Cache.lookup getMessageThreadId convStateCache + -- If the conversation state was defined after processing this + -- message, we should update it. + whenJust mbConversationState \(lastMsgId, _conversationState) -> + when (lastMsgId == msgId) $ + Cache.insert getMessageThreadId (msgId, stateAfter) convStateCache + + let newRefsFound = not $ all (`elem` oldRefs) newRefs -- no new references found, ignoring - when newRefsFound $ withNonEmptyTimeRefs timeRefs \neTimeRefs -> do - Cache.insert msgId timeRefs messageRefsCache + when newRefsFound $ withNonEmptyTimeRefs newRefs \neTimeRefs -> do + -- This cache always keeps only "before" state in order to correctly + -- translate further edits. + Cache.insert msgId (newRefs, stateBefore) messageRefsCache permalink <- getMessagePermalinkCached channelId msgId handleChannelMessageCommon (Just permalink) neTimeRefs handleNewMessage :: BotM () handleNewMessage = do - withNonEmptyTimeRefs timeRefs $ \neTimeRefs -> do + convStateCache <- asks bsConversationStateCache + conversationState <- + fmap (fromMaybe emptyTimeContext . fmap snd . join) $ + traverse (\t -> Cache.lookup t convStateCache) mbThreadId + (timeRefs, newState) <- + getTimeReferencesAndNewStateFromMessage conversationState msg + when (not $ null timeRefs) $ -- save message only if time references are present - asks bsMessageCache >>= Cache.insert msgId timeRefs + asks bsMessageCache >>= Cache.insert msgId (timeRefs, newState) + Cache.insert getMessageThreadId (msgId, newState) convStateCache + asks bsMessageCache >>= Cache.insert msgId (timeRefs, conversationState) + + withNonEmptyTimeRefs timeRefs $ \neTimeRefs -> do handleChannelMessageCommon Nothing neTimeRefs handleChannelMessageCommon :: Maybe Text -> NonEmpty TimeReference -> BotM () @@ -195,8 +220,9 @@ processMessageEvent' evt mEventType sender timeRefs = ephemeralsMailing channelId sendActionLocal handleDirectMessage :: BotM () - handleDirectMessage = - when (mEventType /= METMessageEdited) $ + handleDirectMessage = when (mEventType /= METMessageEdited) $ do + (timeRefs, _stateAfter) <- + getTimeReferencesAndNewStateFromMessage emptyTimeContext msg withNonEmptyTimeRefs timeRefs $ \neTimeRefs -> do -- According to -- https://forums.slackcommunity.com/s/question/0D53a00008vsItQCAU diff --git a/src/TzBot/RunMonad.hs b/src/TzBot/RunMonad.hs index 061ab89..e234397 100644 --- a/src/TzBot/RunMonad.hs +++ b/src/TzBot/RunMonad.hs @@ -17,6 +17,7 @@ import TzBot.Cache (TzCache) import TzBot.Config.Types (BotConfig) import TzBot.Feedback.Dialog.Types (ReportDialogEntry, ReportDialogId) import TzBot.Slack.API +import TzBot.TimeContext (TimeContext) import TzBot.TimeReference import TzBot.Util (postfixFields) @@ -32,8 +33,13 @@ data BotState = BotState , bsUserInfoCache :: TzCache UserId User , bsConversationMembersCache :: TzCache ChannelId (S.Set UserId) , bsReportEntries :: TzCache ReportDialogId ReportDialogEntry - , bsMessageCache :: TzCache MessageId [TimeReference] + , bsMessageCache :: TzCache MessageId ([TimeReference], TimeContext) + -- ^ Used for keeping relevant time references and conversation state + -- that was _before_ this message, i.e. applied to time refs of this message. , bsMessageLinkCache :: TzCache MessageId Text + , bsConversationStateCache :: TzCache ThreadId (MessageId, TimeContext) + -- ^ State of a thread: current state and ID of a message which is origin + -- of that state , bsLogNamespace :: K.Namespace , bsLogContext :: K.LogContexts , bsLogEnv :: K.LogEnv diff --git a/src/TzBot/Slack/API.hs b/src/TzBot/Slack/API.hs index 229f48c..4de577c 100644 --- a/src/TzBot/Slack/API.hs +++ b/src/TzBot/Slack/API.hs @@ -194,7 +194,7 @@ instance FromJSON ChannelType where newtype ThreadId = ThreadId { unThreadId :: Text } deriving stock (Eq, Show) - deriving newtype (ToHttpApiData, FromJSON, ToJSON, Buildable) + deriving newtype (ToHttpApiData, FromJSON, ToJSON, Buildable, Hashable) newtype MessageId = MessageId { unMessageId :: Text } deriving stock (Eq, Show, Ord) diff --git a/src/TzBot/TZ.hs b/src/TzBot/TZ.hs index 531af8d..1015718 100644 --- a/src/TzBot/TZ.hs +++ b/src/TzBot/TZ.hs @@ -24,7 +24,8 @@ import Data.Time.Zones.Types (TZ(..)) import Data.Vector qualified as VB import Data.Vector.Unboxed qualified as VU -import TzBot.TimeReference (DateReference(..), TimeRefSuccess(..), TimeReference(..)) +import TzBot.TimeReference + (DateReference(..), TimeRefSuccess(..), TimeReference, TimeReferenceGeneric(..)) import TzBot.Util (NamedOffset, Offset(..)) -- | Represents a specific change in offset. diff --git a/src/TzBot/TimeContext.hs b/src/TzBot/TimeContext.hs new file mode 100644 index 0000000..542238c --- /dev/null +++ b/src/TzBot/TimeContext.hs @@ -0,0 +1,23 @@ + +-- SPDX-FileCopyrightText: 2022 Serokell +-- +-- SPDX-License-Identifier: MPL-2.0 + +module TzBot.TimeContext where + +import Universum hiding (many, toList, try) + +import Control.Lens.TH (makeLensesWith) +import TzBot.Instances () +import TzBot.TimeReference +import TzBot.Util + +data TimeContext = TimeContext + { tcCurrentDateRef :: Maybe (Matched DateReference) + , tcCurrentLocRef :: Maybe (Matched LocationReference) + } deriving stock (Show, Eq, Generic) + +emptyTimeContext :: TimeContext +emptyTimeContext = TimeContext Nothing Nothing + +makeLensesWith postfixFields ''TimeContext diff --git a/src/TzBot/TimeReference.hs b/src/TzBot/TimeReference.hs index f6d5c89..0aab25e 100644 --- a/src/TzBot/TimeReference.hs +++ b/src/TzBot/TimeReference.hs @@ -33,14 +33,44 @@ We use this type alias to make this distinction a bit more clear. -} type TimeReferenceText = Text +-- | Datatype for keeping value together with its parsed text (as a sequence of tokens) +data Matched a = Matched + { mtText :: Text + -- ^ Consumed text + , mtValue :: a + -- ^ Parsed value + } deriving stock (Show, Eq, Generic, Functor, Foldable, Traversable) + +-- TODO: use lenses +modifyText :: (Text -> Text) -> Matched a -> Matched a +modifyText f Matched {..} = Matched {mtText = f mtText, ..} + +type family WhetherMatched f x where + WhetherMatched Identity x = x + WhetherMatched Matched x = Matched x + -- | A reference to a point in time, e.g. "tuesday at 10am", "3pm CST on July 7th" -data TimeReference = TimeReference +data TimeReferenceGeneric f = TimeReference { trText :: TimeReferenceText -- ^ The original section of the text from where this `TimeReference` was parsed. , trTimeOfDay :: TimeOfDay - , trDateRef :: Maybe DateReference - , trLocationRef :: Maybe LocationReference + , trDateRef :: Maybe (WhetherMatched f DateReference) + , trLocationRef :: Maybe (WhetherMatched f LocationReference) + } + +deriving stock instance Show TimeReference +deriving stock instance Eq TimeReference +deriving stock instance Show TimeReferenceMatched +deriving stock instance Eq TimeReferenceMatched + +type TimeReference = TimeReferenceGeneric Identity +type TimeReferenceMatched = TimeReferenceGeneric Matched + +matchedToPlain :: TimeReferenceMatched -> TimeReference +matchedToPlain TimeReference {..} = TimeReference + { trDateRef = fmap mtValue trDateRef + , trLocationRef = fmap mtValue trLocationRef + , .. } - deriving stock (Eq, Show) getTzLabelMaybe :: TZLabel -> TimeReference -> Maybe TZLabel getTzLabelMaybe senderTz timeRef = case trLocationRef timeRef of diff --git a/src/TzBot/Util.hs b/src/TzBot/Util.hs index 8d7c6ea..f16badf 100644 --- a/src/TzBot/Util.hs +++ b/src/TzBot/Util.hs @@ -213,3 +213,10 @@ secondsPerMinute = 60 tztimeOffset :: TZTime -> Offset tztimeOffset = Offset . timeZoneMinutes . tzTimeOffset + +whenJustFunc :: Maybe b -> (b -> a -> a) -> a -> a +whenJustFunc Nothing _f = id +whenJustFunc (Just b) f = f b + +whenFunc :: Bool -> (a -> a) -> a -> a +whenFunc b f = if b then f else id diff --git a/test/Test/TzBot/GetTimeshiftsSpec.hs b/test/Test/TzBot/GetTimeshiftsSpec.hs index 42d12eb..33a4aa2 100644 --- a/test/Test/TzBot/GetTimeshiftsSpec.hs +++ b/test/Test/TzBot/GetTimeshiftsSpec.hs @@ -18,7 +18,7 @@ import Test.Tasty (TestTree, testGroup) import Test.Tasty.HUnit (Assertion, assertFailure, testCase, (@?=)) import Text.Interpolation.Nyan -import TzBot.Parser (parseTimeRefs) +import TzBot.Parser (parseWithEmptyContext) import TzBot.TZ (TimeShift(..), checkForTimeshifts, checkForTimeshifts') import TzBot.TimeReference (TimeReferenceToUTCResult(..), timeReferenceToUTC) import TzBot.Util @@ -120,7 +120,7 @@ test_checkForTimeshifts = where check :: UTCTime -> Text -> TZLabel -> TZLabel -> [TimeShift] -> Assertion check now input senderTimeZone receiverTimeZone expectedTimeShifts = do - case parseTimeRefs input of + case parseWithEmptyContext input of [timeRef] -> case timeReferenceToUTC senderTimeZone now timeRef of TRTUSuccess timeRefSuccess -> diff --git a/test/Test/TzBot/ParserSpec.hs b/test/Test/TzBot/ParserSpec.hs new file mode 100644 index 0000000..0c3f7c0 --- /dev/null +++ b/test/Test/TzBot/ParserSpec.hs @@ -0,0 +1,187 @@ +-- SPDX-FileCopyrightText: 2022 Serokell +-- +-- SPDX-License-Identifier: MPL-2.0 + +module Test.TzBot.ParserSpec + ( test_parserSpec + ) where + +import Universum + +import Data.Text qualified as T +import Data.Time (DayOfWeek(..), TimeOfDay(..), defaultTimeLocale, formatTime) +import Test.Tasty +import Test.Tasty.HUnit (Assertion, assertFailure, testCase) +import Test.Tasty.Runners (TestTree(TestGroup)) +import Text.Interpolation.Nyan (int, rmode', rmode's) + +import TzBot.Parser (parseWithEmptyContext) +import TzBot.TimeReference + (DateReference(..), LocationReference(..), TimeReference, TimeReferenceGeneric(..), + TimeZoneAbbreviationInfo(..)) + +{- | This test suite contains only tests whose output is too big + - to be placed in doctests + -} +test_parserSpec :: TestTree +test_parserSpec = TestGroup "ParserBig" + [ testCase "First slashed term contains all references, second slashed term contains no refs" $ + mkTestCase + "How about Wednesday at 10:00 / 11:00 UTC or 14:00 / 15:00" + [ TimeReference + "Wednesday at 10:00 UTC" + (TimeOfDay 10 00 00) + (Just (DayOfWeekRef Wednesday)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + , TimeReference + "Wednesday 11:00 UTC" + (TimeOfDay 11 00 00) + (Just (DayOfWeekRef Wednesday)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + , TimeReference + "14:00 (Wednesday) (UTC)" + (TimeOfDay 14 00 00) + (Just (DayOfWeekRef Wednesday)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + , TimeReference + "15:00 (Wednesday) (UTC)" + (TimeOfDay 15 00 00) + (Just (DayOfWeekRef Wednesday)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + ] + , testCase "First slashed term has day of week, second has also UTC" $ + mkTestCase + "How about Wednesday at 10:00 / 11:00 OR 14:00 / 15:00 at Thursday UTC" + [ TimeReference + "Wednesday at 10:00 (UTC)" + (TimeOfDay 10 00 00) + (Just (DayOfWeekRef Wednesday)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + , TimeReference + "Wednesday 11:00 (UTC)" + (TimeOfDay 11 00 00) + (Just (DayOfWeekRef Wednesday)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + , TimeReference + "14:00 at Thursday UTC" + (TimeOfDay 14 00 00) + (Just (DayOfWeekRef Thursday)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + , TimeReference + "15:00 at Thursday UTC" + (TimeOfDay 15 00 00) + (Just (DayOfWeekRef Thursday)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + ] + , testCase "Some hyphenated intervals, separate date reference" $ + mkTestCase + "Hi guys! Let’s have a sync call tomorrow? Almost every time from 7am-2pm UTC works (except 10:30am - 12pm UTC)" + [ TimeReference + "7am UTC (tomorrow)" + (TimeOfDay 07 00 00) + (Just (DaysFromToday 1)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + , TimeReference + "2pm UTC (tomorrow)" + (TimeOfDay 14 00 00) + (Just (DaysFromToday 1)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + , TimeReference + "10:30am UTC (tomorrow)" + (TimeOfDay 10 30 00) + (Just (DaysFromToday 1)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + , TimeReference + "12pm UTC (tomorrow)" + (TimeOfDay 12 00 00) + (Just (DaysFromToday 1)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + ] + , testCase "Pick last date reference" $ + mkTestCase + "I wanted to meet tomorrow, but seems it's not possible... maybe 3rd march? Let's try something between 10am and 11am UTC" + [ TimeReference + "10am UTC (3rd march)" + (TimeOfDay 10 00 00) + (Just (DayOfMonthRef 3 (Just (3,Nothing)))) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + , TimeReference + "11am UTC (3rd march)" + (TimeOfDay 11 00 00) + (Just (DayOfMonthRef 3 (Just (3,Nothing)))) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + ] + , testCase "Using location reference from previous full time reference" $ + mkTestCase + "How about tomorrow 8am-12am UTC? For me 9am is the most perfect time" + [ TimeReference + "tomorrow 8am UTC" + (TimeOfDay 08 00 00) + (Just (DaysFromToday 1)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + , TimeReference + "tomorrow 12am UTC" + (TimeOfDay 12 00 00) + (Just (DaysFromToday 1)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + , TimeReference + "9am (tomorrow) (UTC)" + (TimeOfDay 09 00 00) + (Just (DaysFromToday 1)) + (Just (TimeZoneAbbreviationRef (TimeZoneAbbreviationInfo {tzaiAbbreviation = "UTC", tzaiOffsetMinutes = 0, tzaiFullName = "UTC"}))) + ] + ] + +mkTestCase :: HasCallStack => Text -> [TimeReference] -> Assertion +mkTestCase input expectedRefs = do + let outputRefs = parseWithEmptyContext input + assertRefPairs expectedRefs outputRefs + +assertRefPairs :: HasCallStack => [TimeReference] -> [TimeReference] -> Assertion +assertRefPairs [] [] = pass +assertRefPairs [] os = + assertFailure + [int|| + Expected no more time references, but got + #{prettyPrintList os} + |] +assertRefPairs es [] = + assertFailure + [int|| + Expected more time references #{prettyPrintList es} + |] +assertRefPairs (e : es) (o : os) = + assertRefPair e o >> assertRefPairs es os + +prettyPrintTimeReference :: Char -> TimeReference -> Text +prettyPrintTimeReference start TimeReference {..} = + [int|s| + #{start} TimeReference + #s{trText} + (#{renderTimeOfDay trTimeOfDay}) + (#s{trDateRef}) + (#s{trLocationRef}) + |] + where + renderTimeOfDay (t :: TimeOfDay) = formatTime defaultTimeLocale "TimeOfDay %H %M %S" t + +prettyPrintList :: [TimeReference] -> Text +prettyPrintList [] = "Empty list" +prettyPrintList (t : ts) = + T.unlines $ prettyPrintTimeReference '[' t + : map (prettyPrintTimeReference ',') ts + <> ["]"] + +assertRefPair :: HasCallStack => TimeReference -> TimeReference -> Assertion +assertRefPair expTr outTr = do + assertUnit "Text" trText + assertUnit "Date reference" trDateRef + assertUnit "Location reference" trLocationRef + assertUnit "Time of day" trTimeOfDay + where + assertUnit :: (Show a, Eq a) => Text -> (TimeReference -> a) -> Assertion + assertUnit note getter = do + let expUnit = getter expTr + outUnit = getter outTr + when (expUnit /= outUnit) $ + assertFailure [int||#{note}: expected #s{expUnit} but got #s{outUnit}|] diff --git a/test/Test/TzBot/RenderSpec.hs b/test/Test/TzBot/RenderSpec.hs index 702c4d9..04dd51d 100644 --- a/test/Test/TzBot/RenderSpec.hs +++ b/test/Test/TzBot/RenderSpec.hs @@ -18,7 +18,7 @@ import Test.Tasty (TestTree) import Test.Tasty.HUnit (Assertion, testCase, (@?=)) import Test.Tasty.Runners (TestTree(..)) -import TzBot.Parser (parseTimeRefs) +import TzBot.Parser (parseWithEmptyContext) import TzBot.Render import TzBot.Slack.API @@ -246,7 +246,7 @@ translWithCommonNote q w e = TranslationPair q w (Just e) (Just e) mkTestCase :: ModalFlag -> UTCTime -> Text -> User -> User -> [TranslationPair] -> Assertion mkTestCase modalFlag eventTimestamp refText sender otherUser expectedOtherUserTransl = do - let [timeRef] = parseTimeRefs refText + let [timeRef] = parseWithEmptyContext refText ephemeralTemplate = renderTemplate modalFlag eventTimestamp sender $ NE.singleton timeRef diff --git a/tzbot.cabal b/tzbot.cabal index 5adc9da..5ef774c 100644 --- a/tzbot.cabal +++ b/tzbot.cabal @@ -54,6 +54,7 @@ library TzBot.Slack.Events.ViewPayload TzBot.Slack.Fixtures TzBot.Slack.Modal + TzBot.TimeContext TzBot.TimeReference TzBot.TZ TzBot.Util @@ -301,6 +302,7 @@ test-suite tzbot-test Test.TzBot.GetTimeshiftsSpec Test.TzBot.HandleTooManyRequests Test.TzBot.MessageBlocksSpec + Test.TzBot.ParserSpec Test.TzBot.RenderSpec Test.TzBot.TimeReferenceToUtcSpec Tree @@ -376,6 +378,7 @@ test-suite tzbot-test , tasty-hspec , tasty-hunit , tasty-quickcheck + , text , time , tzbot , tztime