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.

173 lines
6.2 KiB

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