SimpleX-Chat/apps/simplex-broadcast-bot/Main.hs
Evgeny Poberezkin a0351d6f99
apps: update chat bots, readme (#1928)
* apps: update chat bots, readme

* CLI readme

* broadcast bot

* delete messages from non-publishers, better replies, support forwarding low-res images and links

* typo

Co-authored-by: spaced4ndy <8711996+spaced4ndy@users.noreply.github.com>

* change

---------

Co-authored-by: spaced4ndy <8711996+spaced4ndy@users.noreply.github.com>
2023-02-14 07:57:27 +00:00

74 lines
2.9 KiB
Haskell

{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Control.Concurrent.Async
import Control.Concurrent.STM
import Control.Monad.Reader
import qualified Data.Text as T
import Options
import Simplex.Chat.Bot
import Simplex.Chat.Controller
import Simplex.Chat.Core
import Simplex.Chat.Messages
import Simplex.Chat.Options
import Simplex.Chat.Protocol (MsgContent (..))
import Simplex.Chat.Terminal (terminalChatConfig)
import Simplex.Chat.Types
import System.Directory (getAppUserDataDirectory)
main :: IO ()
main = do
opts@BroadcastBotOpts {chatOptions} <- welcomeGetOpts
simplexChatCore terminalChatConfig chatOptions Nothing $ broadcastBot opts
welcomeGetOpts :: IO BroadcastBotOpts
welcomeGetOpts = do
appDir <- getAppUserDataDirectory "simplex"
opts@BroadcastBotOpts {chatOptions = ChatOpts {dbFilePrefix}} <- getBroadcastBotOpts appDir "simplex_status_bot"
putStrLn $ "SimpleX Chat Bot v" ++ versionNumber
putStrLn $ "db: " <> dbFilePrefix <> "_chat.db, " <> dbFilePrefix <> "_agent.db"
pure opts
broadcastBot :: BroadcastBotOpts -> User -> ChatController -> IO ()
broadcastBot BroadcastBotOpts {publishers, welcomeMessage, prohibitedMessage} _user cc = do
initializeBotAddress cc
race_ (forever $ void getLine) . forever $ do
(_, resp) <- atomically . readTBQueue $ outputQ cc
case resp of
CRContactConnected _ ct _ -> do
contactConnected ct
sendMessage cc ct welcomeMessage
CRNewChatItem _ (AChatItem _ SMDRcv (DirectChat ct) ci@ChatItem {content = CIRcvMsgContent mc})
| publisher `elem` publishers ->
if allowContent mc
then do
sendChatCmd cc "/contacts" >>= \case
CRContactsList _ cts -> do
let cts' = filter broadcastTo cts
forM_ cts' $ \ct' -> sendComposedMessage cc ct' Nothing mc
sendReply $ "Forwarded to " <> show (length cts') <> " contact(s)"
r -> putStrLn $ "Error getting contacts list: " <> show r
else sendReply "!1 Message is not supported!"
| otherwise -> do
sendReply prohibitedMessage
deleteMessage cc ct $ chatItemId' ci
where
sendReply = sendComposedMessage cc ct (Just $ chatItemId' ci) . textMsgContent
publisher = Publisher {contactId = contactId' ct, localDisplayName = localDisplayName' ct}
allowContent = \case
MCText _ -> True
MCLink {} -> True
MCImage {} -> True
_ -> False
broadcastTo ct'@Contact {activeConn = conn@Connection {connStatus}} =
(connStatus == ConnSndReady || connStatus == ConnReady)
&& not (connDisabled conn)
&& contactId' ct' /= contactId' ct
_ -> pure ()
where
contactConnected ct = putStrLn $ T.unpack (localDisplayName' ct) <> " connected"