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.

160 lines
6.6 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
  1. {-# LANGUAGE OverloadedStrings #-}
  2. {-# LANGUAGE RecordWildCards #-}
  3. {-# LANGUAGE ScopedTypeVariables #-}
  4. module Main where
  5. import Control.Monad (when, void)
  6. import qualified Data.Text as T
  7. import qualified Data.Text.IO as TIO
  8. import Control.Monad.IO.Unlift (toIO, liftIO, withRunInIO)
  9. import Discord ( def, restCall
  10. , runDiscord, sendCommand
  11. , DiscordHandler
  12. , RunDiscordOpts(..)
  13. )
  14. import Discord.Types ( Event(..), PartialApplication(..)
  15. , GatewaySendable(..)
  16. , UpdateStatusOpts(..)
  17. , UpdateStatusType(..)
  18. , Activity(..), ActivityType(..)
  19. )
  20. import Discord.Interactions ( interactionResponseBasic
  21. , Interaction(..)
  22. , InteractionDataApplicationCommand(..)
  23. )
  24. import qualified Discord.Requests as R
  25. import Commands ( edtResponse, edtCommand
  26. , pingResponse, pingCommand
  27. , remindResponse, remindCommand
  28. , groupCommand, groupResponse
  29. , helpCommand, helpResponse
  30. , Remind(..)
  31. )
  32. import Conf ( Config(..), Group(..), readConfig )
  33. import qualified System.Cron.Schedule as Cron
  34. import qualified Data.Map.Strict as Map
  35. import Commands.EDT (getEdt)
  36. import qualified Control.Concurrent
  37. import qualified Control.Event as E
  38. import UnliftIO.Directory (doesFileExist, removeFile)
  39. main :: IO ()
  40. main = do
  41. tok <- TIO.readFile "./auth.secret"
  42. conf <- readConfig "./conf.yaml"
  43. eventSystem <- E.initEventSystem
  44. err <- runDiscord $ def { discordToken = tok
  45. , discordOnStart = onDiscordStart conf eventSystem
  46. , discordOnEnd = liftIO $ putStrLn "Ended"
  47. , discordOnEvent = onDiscordEvent conf eventSystem
  48. , discordOnLog =
  49. \s -> TIO.putStrLn s >> TIO.putStrLn ""
  50. }
  51. TIO.putStrLn err
  52. onDiscordStart :: Config -> E.EventSystem -> DiscordHandler ()
  53. onDiscordStart conf eventSystem = do
  54. let
  55. activity :: Activity
  56. activity = def { activityName = "Doing stuff"
  57. , activityType = ActivityTypeGame
  58. , activityUrl = Nothing
  59. }
  60. opts :: UpdateStatusOpts
  61. opts = UpdateStatusOpts { updateStatusOptsSince = Nothing
  62. , updateStatusOptsGame = Just activity
  63. , updateStatusOptsNewStatus = UpdateStatusOnline
  64. , updateStatusOptsAFK = False
  65. }
  66. sendCommand (UpdateStatus opts)
  67. remindDataExist <- liftIO $ doesFileExist "reminds.data"
  68. when remindDataExist $ do
  69. remindfile <- liftIO $ readFile "reminds.data"
  70. let reminddata :: [Remind]
  71. reminddata = map read $ lines remindfile
  72. mapM_ (\r -> do
  73. withRunInIO $ \runInIO ->
  74. E.addEvent eventSystem (rmdWhen r)
  75. ( do
  76. runInIO ( restCall
  77. $ R.CreateMessage (rmdWhere r)
  78. $ "<@"
  79. `T.append` T.pack (show $rmdWho r)
  80. `T.append` "> **Reminder**\n"
  81. `T.append` rmdWhat r
  82. )
  83. return ()
  84. )
  85. ) reminddata
  86. liftIO $ removeFile "reminds.data"
  87. onDiscordEvent :: Config -> E.EventSystem -> Event -> DiscordHandler ()
  88. onDiscordEvent conf@Config{..} eventSystem (Ready _ _ _ _ _ _ (PartialApplication i _)) = do
  89. mapM_ (maybe ( return () )
  90. ( void
  91. . restCall
  92. . R.CreateGuildApplicationCommand i configServer
  93. )
  94. )
  95. [ pingCommand
  96. , edtCommand conf
  97. , remindCommand
  98. , groupCommand conf
  99. , helpCommand
  100. ]
  101. let glist = Map.toList configGroups
  102. withRunInIO $ \runInIO -> Cron.execSchedule $ do
  103. Cron.addJob ( runInIO
  104. $ pushgroupedt conf "tomorrow" glist
  105. ) configAutoEDTCronDay
  106. Cron.addJob ( runInIO
  107. $ pushgroupedt conf "week" glist
  108. ) configAutoEDTCronWeek
  109. liftIO $ putStrLn "Started"
  110. onDiscordEvent conf@Config{..} eventSystem
  111. ( InteractionCreate InteractionApplicationCommand
  112. { interactionDataApplicationCommand =
  113. InteractionDataApplicationCommandChatInput
  114. { interactionDataApplicationCommandName = name
  115. , interactionDataApplicationCommandOptions = opts
  116. , ..
  117. }
  118. , interactionChannelId = Just channel
  119. , interactionGuildId = Just guild
  120. , interactionUser = user
  121. , ..
  122. }
  123. ) = do
  124. response <- responseIO
  125. void $ restCall
  126. (R.CreateInteractionResponse interactionId interactionToken response)
  127. where
  128. responseIO = case name of
  129. "ping" -> liftIO $ pingResponse conf
  130. "edt" -> liftIO $ edtResponse conf opts
  131. "remind" -> remindResponse opts eventSystem channel user
  132. "group" -> groupResponse conf user guild opts
  133. "help" -> liftIO helpResponse
  134. _ -> return $ interactionResponseBasic $ "Unhandled Command: " `T.append` name
  135. onDiscordEvent _ _ _ = return ()
  136. pushgroupedt :: Config -> T.Text ->[(T.Text, Group)] -> DiscordHandler ()
  137. pushgroupedt conf@Config{..} day glist = do
  138. mapM_ (\(gn, Group{groupChannel = gc}) -> do
  139. edt <- liftIO $ getEdt conf $ Map.fromList [("group", gn), ("day", day )]
  140. liftIO
  141. $ TIO.putStrLn
  142. $ "Putting out time table for group "
  143. `T.append` gn
  144. `T.append` " in "
  145. `T.append` T.pack (show gc)
  146. `T.append` ":\n"
  147. `T.append` edt
  148. restCall $ R.CreateMessage gc (edt `T.append` "\nAutomatic time table")
  149. return ()
  150. ) glist