You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

166 lines
6.1 KiB

3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
3 years ago
  1. {-# LANGUAGE RecordWildCards #-}
  2. {-# LANGUAGE OverloadedStrings #-}
  3. {-# LANGUAGE DataKinds #-}
  4. {-# OPTIONS_GHC -Wno-deferred-out-of-scope-variables #-}
  5. module Commands.EDT
  6. ( getEdt
  7. ) where
  8. import Conf ( Config(..)
  9. , Group(..)
  10. )
  11. import Control.Monad.IO.Class ( MonadIO
  12. , liftIO
  13. )
  14. import qualified Data.Array as Ar
  15. import qualified Data.CaseInsensitive as CI
  16. import Data.List ( sortOn )
  17. import qualified Data.Map.Strict as Map
  18. import Data.Maybe ( fromMaybe )
  19. import qualified Data.Text as TS
  20. import qualified Data.Text.Lazy as T
  21. import qualified Data.Text.Lazy.Encoding as TE
  22. import qualified Data.Time as DT
  23. import qualified Data.Time.Calendar.Easter as DT
  24. import qualified Network.HTTP.Simple as HTTP
  25. import qualified Text.ICalendar.Parser as IP
  26. import qualified Text.ICalendar.Types as IT
  27. import Text.Printf ( printf )
  28. import qualified Text.Regex.PCRE as Re
  29. import qualified Text.URI as Uri
  30. getEdt :: Config -> Map.Map TS.Text TS.Text -> IO TS.Text
  31. getEdt conf@Config {..} opts = do
  32. cal_req <- HTTP.httpLBS req
  33. let cal = IP.parseICalendar
  34. (IP.DecodingFunctions TE.decodeUtf8 (CI.mk . TE.decodeUtf8))
  35. (TS.unpack group)
  36. (HTTP.getResponseBody cal_req)
  37. dates <- readDate date
  38. tz <- DT.getTimeZone $ DT.UTCTime (head dates) $ DT.secondsToDiffTime 43200
  39. let
  40. message =
  41. case
  42. (case cal of
  43. Left _ -> "I don't know this group, alternatively ADE doesn't work"
  44. Right (vcal@IT.VCalendar { IT.vcEvents = evm } : _, _) ->
  45. TS.unlines
  46. . map
  47. (\d -> if not (null (ev d))
  48. then
  49. "**"
  50. `TS.append` TS.pack (show d)
  51. `TS.append` "**\n"
  52. `TS.append` renderEvents tz (ev d)
  53. else ""
  54. )
  55. $ dates
  56. where
  57. ev :: DT.Day -> [IT.VEvent]
  58. ev d =
  59. sortOn IT.veDTStart
  60. . filter (inDate d)
  61. . map snd
  62. . Map.toList
  63. $ evm
  64. _ -> "An unexpected error has occured"
  65. )
  66. of
  67. "" -> "No classes for the selected period"
  68. s -> s
  69. return message
  70. where
  71. group :: TS.Text
  72. group = fromMaybe "" $ Map.lookup "group" opts
  73. date :: TS.Text
  74. date = fromMaybe "week" $ Map.lookup "day" opts
  75. url :: String
  76. url =
  77. TS.unpack
  78. . groupAde
  79. . fromMaybe (Group 0 0 dummyAddress)
  80. . (`Map.lookup` configGroups)
  81. . fromMaybe ""
  82. . Map.lookup "group"
  83. $ opts
  84. req = HTTP.parseRequest_ url
  85. -- not a place where you'll find valid ICS so we know the group must be wrong
  86. dummyAddress :: TS.Text
  87. dummyAddress = "https://example.com"
  88. readDate :: TS.Text -> IO [DT.Day]
  89. readDate dtT = do
  90. DT.UTCTime today _ <- DT.getCurrentTime
  91. return $ case TS.unpack dtT of
  92. "today" -> [today]
  93. "tomorrow" -> [DT.addDays 1 today]
  94. "week" -> map (`DT.addDays` lastSunday) [1 .. 7] where
  95. lastweek :: DT.Day
  96. lastweek = DT.addDays (-6) today
  97. lastSunday = DT.sundayAfter lastweek
  98. [dd, du, '/', md, mu, '/', yk, yh, yd, yu] ->
  99. [DT.fromGregorian (read [yk, yh, yd, yu]) (read [md, mu]) (read [dd, du])]
  100. _ -> [today]
  101. inDate :: DT.Day -> IT.VEvent -> Bool
  102. inDate date ev@IT.VEvent { veDTStart = mdts } = evDay == date
  103. where
  104. evDay :: DT.Day
  105. evDay = case mdts of
  106. Just dts -> case dts of
  107. IT.DTStartDateTime dt _ -> case dt of
  108. IT.FloatingDateTime lt -> DT.localDay lt
  109. IT.UTCDateTime ut -> DT.utctDay ut
  110. IT.ZonedDateTime lt _ -> DT.localDay lt
  111. IT.DTStartDate da _ -> IT.dateValue da
  112. Nothing -> DT.fromGregorian 0 0 0
  113. renderEvents :: DT.TimeZone -> [IT.VEvent] -> TS.Text
  114. renderEvents tz = TS.unlines . map renderEvent
  115. where
  116. renderEvent :: IT.VEvent -> TS.Text
  117. renderEvent ev = TS.pack $ printf
  118. "*%02d:%02d → %02d:%02d* : **%s** with **%s** in **%s**"
  119. (DT.todHour $ startT ev)
  120. (DT.todMin $ startT ev)
  121. (DT.todHour $ endT ev)
  122. (DT.todMin $ endT ev)
  123. (summary ev)
  124. (teacher ev)
  125. (room ev)
  126. startT :: IT.VEvent -> DT.TimeOfDay
  127. startT IT.VEvent { veDTStart = Just (IT.DTStartDateTime dt _) } = case dt of
  128. IT.FloatingDateTime lt -> DT.localTimeOfDay lt
  129. IT.UTCDateTime ut ->
  130. snd . DT.utcToLocalTimeOfDay tz . DT.timeToTimeOfDay $ DT.utctDayTime ut
  131. IT.ZonedDateTime lt _ -> DT.localTimeOfDay lt
  132. startT _ = DT.TimeOfDay 0 0 0
  133. endT :: IT.VEvent -> DT.TimeOfDay
  134. endT IT.VEvent { veDTEndDuration = Just (Left (IT.DTEndDateTime dt _)) } =
  135. case dt of
  136. IT.FloatingDateTime lt -> DT.localTimeOfDay lt
  137. IT.UTCDateTime ut ->
  138. snd . DT.utcToLocalTimeOfDay tz . DT.timeToTimeOfDay $ DT.utctDayTime ut
  139. IT.ZonedDateTime lt txt -> DT.localTimeOfDay lt
  140. endT _ = DT.TimeOfDay 0 0 0
  141. summary IT.VEvent { veSummary = Just IT.Summary { summaryValue = x } } = x
  142. summary _ = "Unknown"
  143. room IT.VEvent { veLocation = Just IT.Location { locationValue = x } } = x
  144. room _ = "Unknown"
  145. teacher :: IT.VEvent -> String
  146. teacher IT.VEvent { veDescription = Just IT.Description { descriptionValue = val } }
  147. = if '\n' `elem` teacher' then "Unknown" else teacher'
  148. where
  149. teacher' = if uncurry (>) (Ar.bounds marray)
  150. then "Unknown"
  151. else fst . last . Ar.elems $ marray
  152. marray = if null matches then Ar.listArray (1, 0) [] else head matches
  153. matches = Re.matchAllText teacherRe $ T.unpack val
  154. teacher _ = "Unknown"
  155. teacherRe = Re.makeRegexOpts Re.compMultiline
  156. Re.execBlank
  157. ("^\\n\\n.+\\n(.+)\\n" :: String)