terminal: refactor chat core used in terminal app and in bot examples (#516)

* terminal: refactor chat core used in terminal app and in bot examples

* fix tests

* refactor
This commit is contained in:
Evgeny Poberezkin 2022-04-10 17:13:06 +01:00 committed by GitHub
parent 0ac9785e4b
commit fa313caa82
No known key found for this signature in database
GPG key ID: 4AEE18F83AFDEB23
10 changed files with 73 additions and 77 deletions

View file

@ -14,6 +14,7 @@ import qualified Data.Text as T
import Simplex.Chat import Simplex.Chat
import Simplex.Chat.Bot import Simplex.Chat.Bot
import Simplex.Chat.Controller import Simplex.Chat.Controller
import Simplex.Chat.Core
import Simplex.Chat.Messages import Simplex.Chat.Messages
import Simplex.Chat.Options import Simplex.Chat.Options
import Simplex.Chat.Types import Simplex.Chat.Types
@ -23,7 +24,7 @@ import Text.Read
main :: IO () main :: IO ()
main = do main = do
opts <- welcomeGetOpts opts <- welcomeGetOpts
simplexChatBot defaultChatConfig opts mySquaringBot simplexChatCore defaultChatConfig opts Nothing mySquaringBot
welcomeGetOpts :: IO ChatOpts welcomeGetOpts :: IO ChatOpts
welcomeGetOpts = do welcomeGetOpts = do
@ -50,5 +51,5 @@ mySquaringBot _user cc = do
Just n -> msg <> " * " <> msg <> " = " <> show (n * n) Just n -> msg <> " * " <> msg <> " = " <> show (n * n)
_ -> pure () _ -> pure ()
where where
sendMsg Contact {contactId} msg = sendCmd cc $ "/_send @" <> show contactId <> " text " <> msg sendMsg Contact {contactId} msg = sendChatCmd cc $ "/_send @" <> show contactId <> " text " <> msg
contactConnected Contact {localDisplayName} = putStrLn $ T.unpack localDisplayName <> " connected" contactConnected Contact {localDisplayName} = putStrLn $ T.unpack localDisplayName <> " connected"

View file

@ -5,6 +5,7 @@ module Main where
import Simplex.Chat import Simplex.Chat
import Simplex.Chat.Bot import Simplex.Chat.Bot
import Simplex.Chat.Controller (versionNumber) import Simplex.Chat.Controller (versionNumber)
import Simplex.Chat.Core
import Simplex.Chat.Options import Simplex.Chat.Options
import System.Directory (getAppUserDataDirectory) import System.Directory (getAppUserDataDirectory)
import Text.Read import Text.Read
@ -12,7 +13,7 @@ import Text.Read
main :: IO () main :: IO ()
main = do main = do
opts <- welcomeGetOpts opts <- welcomeGetOpts
simplexChatBot defaultChatConfig opts $ simplexChatCore defaultChatConfig opts Nothing $
chatBotRepl "Hello! I am a simple squaring bot - if you send me a number, I will calculate its square" $ \msg -> chatBotRepl "Hello! I am a simple squaring bot - if you send me a number, I will calculate its square" $ \msg ->
case readMaybe msg :: Maybe Integer of case readMaybe msg :: Maybe Integer of
Just n -> msg <> " * " <> msg <> " = " <> show (n * n) Just n -> msg <> " * " <> msg <> " = " <> show (n * n)

View file

@ -4,17 +4,14 @@ module Main where
import Control.Concurrent (threadDelay) import Control.Concurrent (threadDelay)
import Simplex.Chat import Simplex.Chat
import Simplex.Chat.Bot import Simplex.Chat.Controller (versionNumber)
import Simplex.Chat.Controller (ChatConfig, versionNumber) import Simplex.Chat.Core
import Simplex.Chat.Options import Simplex.Chat.Options
import Simplex.Chat.Terminal import Simplex.Chat.Terminal
import Simplex.Chat.View (serializeChatResponse) import Simplex.Chat.View (serializeChatResponse)
import System.Directory (getAppUserDataDirectory) import System.Directory (getAppUserDataDirectory)
import System.Terminal (withTerminal) import System.Terminal (withTerminal)
cfg :: ChatConfig
cfg = defaultChatConfig
main :: IO () main :: IO ()
main = do main = do
appDir <- getAppUserDataDirectory "simplex" appDir <- getAppUserDataDirectory "simplex"
@ -23,9 +20,9 @@ main = do
then do then do
welcome opts welcome opts
t <- withTerminal pure t <- withTerminal pure
simplexChat cfg opts t simplexChatTerminal defaultChatConfig opts t
else simplexChatBot cfg opts $ \_ cc -> do else simplexChatCore defaultChatConfig opts Nothing $ \_ cc -> do
r <- sendCmd cc chatCmd r <- sendChatCmd cc chatCmd
putStrLn $ serializeChatResponse r putStrLn $ serializeChatResponse r
threadDelay $ chatCmdDelay opts * 1000000 threadDelay $ chatCmdDelay opts * 1000000

View file

@ -22,6 +22,7 @@ library
Simplex.Chat Simplex.Chat
Simplex.Chat.Bot Simplex.Chat.Bot
Simplex.Chat.Controller Simplex.Chat.Controller
Simplex.Chat.Core
Simplex.Chat.Help Simplex.Chat.Help
Simplex.Chat.Markdown Simplex.Chat.Markdown
Simplex.Chat.Messages Simplex.Chat.Messages

View file

@ -100,10 +100,11 @@ defaultSMPServers =
logCfg :: LogConfig logCfg :: LogConfig
logCfg = LogConfig {lc_file = Nothing, lc_stderr = True} logCfg = LogConfig {lc_file = Nothing, lc_stderr = True}
newChatController :: SQLiteStore -> Maybe User -> ChatConfig -> ChatOpts -> (Notification -> IO ()) -> IO ChatController newChatController :: SQLiteStore -> Maybe User -> ChatConfig -> ChatOpts -> Maybe (Notification -> IO ()) -> IO ChatController
newChatController chatStore user cfg@ChatConfig {agentConfig = aCfg, tbqSize} ChatOpts {dbFilePrefix, smpServers, logConnections} sendNotification = do newChatController chatStore user cfg@ChatConfig {agentConfig = aCfg, tbqSize} ChatOpts {dbFilePrefix, smpServers, logConnections} sendToast = do
let f = chatStoreFile dbFilePrefix let f = chatStoreFile dbFilePrefix
let config = cfg {subscriptionEvents = logConnections} config = cfg {subscriptionEvents = logConnections}
sendNotification = fromMaybe (const $ pure ()) sendToast
activeTo <- newTVarIO ActiveNone activeTo <- newTVarIO ActiveNone
firstTime <- not <$> doesFileExist f firstTime <- not <$> doesFileExist f
currentUser <- newTVarIO user currentUser <- newTVarIO user

View file

@ -7,40 +7,17 @@ module Simplex.Chat.Bot where
import Control.Concurrent.Async import Control.Concurrent.Async
import Control.Concurrent.STM import Control.Concurrent.STM
import Control.Logger.Simple
import Control.Monad.Reader import Control.Monad.Reader
import qualified Data.ByteString.Char8 as B import qualified Data.ByteString.Char8 as B
import qualified Data.Text as T import qualified Data.Text as T
import Data.Text.Encoding (encodeUtf8)
import Simplex.Chat
import Simplex.Chat.Controller import Simplex.Chat.Controller
import Simplex.Chat.Core
import Simplex.Chat.Messages import Simplex.Chat.Messages
import Simplex.Chat.Options (ChatOpts (..))
import Simplex.Chat.Store import Simplex.Chat.Store
import Simplex.Chat.Types (Contact (..), User (..)) import Simplex.Chat.Types (Contact (..), User (..))
import Simplex.Messaging.Encoding.String (strEncode) import Simplex.Messaging.Encoding.String (strEncode)
import System.Exit (exitFailure) import System.Exit (exitFailure)
simplexChatBot :: ChatConfig -> ChatOpts -> (User -> ChatController -> IO ()) -> IO ()
simplexChatBot cfg@ChatConfig {dbPoolSize, yesToMigrations} opts chatBot
| logAgent opts = do
setLogLevel LogInfo -- LogError
withGlobalLogging logCfg initRun
| otherwise = initRun
where
initRun = do
let f = chatStoreFile $ dbFilePrefix opts
st <- createStore f dbPoolSize yesToMigrations
u <- getCreateActiveUser st
cc <- newChatController st (Just u) cfg opts (const $ pure ())
runSimplexChatBot u cc chatBot
runSimplexChatBot :: User -> ChatController -> (User -> ChatController -> IO ()) -> IO ()
runSimplexChatBot u cc chatBot = do
a1 <- async $ chatBot u cc
a2 <- runReaderT (startChatController u) cc
waitEither_ a1 a2
chatBotRepl :: String -> (String -> String) -> User -> ChatController -> IO () chatBotRepl :: String -> (String -> String) -> User -> ChatController -> IO ()
chatBotRepl welcome answer _user cc = do chatBotRepl welcome answer _user cc = do
initializeBotAddress cc initializeBotAddress cc
@ -55,23 +32,20 @@ chatBotRepl welcome answer _user cc = do
void . sendMsg contact $ answer msg void . sendMsg contact $ answer msg
_ -> pure () _ -> pure ()
where where
sendMsg Contact {contactId} msg = sendCmd cc $ "/_send @" <> show contactId <> " text " <> msg sendMsg Contact {contactId} msg = sendChatCmd cc $ "/_send @" <> show contactId <> " text " <> msg
contactConnected Contact {localDisplayName} = putStrLn $ T.unpack localDisplayName <> " connected" contactConnected Contact {localDisplayName} = putStrLn $ T.unpack localDisplayName <> " connected"
initializeBotAddress :: ChatController -> IO () initializeBotAddress :: ChatController -> IO ()
initializeBotAddress cc = do initializeBotAddress cc = do
sendCmd cc "/show_address" >>= \case sendChatCmd cc "/show_address" >>= \case
CRUserContactLink uri _ -> showBotAddress uri CRUserContactLink uri _ -> showBotAddress uri
CRChatCmdError (ChatErrorStore SEUserContactLinkNotFound) -> do CRChatCmdError (ChatErrorStore SEUserContactLinkNotFound) -> do
putStrLn $ "No bot address, creating..." putStrLn $ "No bot address, creating..."
sendCmd cc "/address" >>= \case sendChatCmd cc "/address" >>= \case
CRUserContactLinkCreated uri -> showBotAddress uri CRUserContactLinkCreated uri -> showBotAddress uri
_ -> putStrLn "can't create bot address" >> exitFailure _ -> putStrLn "can't create bot address" >> exitFailure
_ -> putStrLn "unexpected response" >> exitFailure _ -> putStrLn "unexpected response" >> exitFailure
where where
showBotAddress uri = do showBotAddress uri = do
putStrLn $ "Bot's contact address is: " <> B.unpack (strEncode uri) putStrLn $ "Bot's contact address is: " <> B.unpack (strEncode uri)
void $ sendCmd cc "/auto_accept on" void $ sendChatCmd cc "/auto_accept on"
sendCmd :: ChatController -> String -> IO ChatResponse
sendCmd cc s = runReaderT (execChatCommand . encodeUtf8 $ T.pack s) cc

38
src/Simplex/Chat/Core.hs Normal file
View file

@ -0,0 +1,38 @@
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
module Simplex.Chat.Core where
import Control.Logger.Simple
import Control.Monad.Reader
import qualified Data.Text as T
import Data.Text.Encoding (encodeUtf8)
import Simplex.Chat
import Simplex.Chat.Controller
import Simplex.Chat.Options (ChatOpts (..))
import Simplex.Chat.Store
import Simplex.Chat.Types
import UnliftIO.Async
simplexChatCore :: ChatConfig -> ChatOpts -> Maybe (Notification -> IO ()) -> (User -> ChatController -> IO ()) -> IO ()
simplexChatCore cfg@ChatConfig {dbPoolSize, yesToMigrations} opts sendToast chat
| logAgent opts = do
setLogLevel LogInfo -- LogError
withGlobalLogging logCfg initRun
| otherwise = initRun
where
initRun = do
let f = chatStoreFile $ dbFilePrefix opts
st <- createStore f dbPoolSize yesToMigrations
u <- getCreateActiveUser st
cc <- newChatController st (Just u) cfg opts sendToast
runSimplexChat u cc chat
runSimplexChat :: User -> ChatController -> (User -> ChatController -> IO ()) -> IO ()
runSimplexChat u cc chat = do
a1 <- async $ chat u cc
a2 <- runReaderT (startChatController u) cc
waitEither_ a1 a2
sendChatCmd :: ChatController -> String -> IO ChatResponse
sendChatCmd cc s = runReaderT (execChatCommand . encodeUtf8 $ T.pack s) cc

View file

@ -73,7 +73,7 @@ chatInit dbFilePrefix = do
let f = chatStoreFile dbFilePrefix let f = chatStoreFile dbFilePrefix
chatStore <- createStore f (dbPoolSize defaultMobileConfig) (yesToMigrations (defaultMobileConfig :: ChatConfig)) chatStore <- createStore f (dbPoolSize defaultMobileConfig) (yesToMigrations (defaultMobileConfig :: ChatConfig))
user_ <- getActiveUser_ chatStore user_ <- getActiveUser_ chatStore
newChatController chatStore user_ defaultMobileConfig mobileChatOpts {dbFilePrefix} (const $ pure ()) newChatController chatStore user_ defaultMobileConfig mobileChatOpts {dbFilePrefix} Nothing
chatSendCmd :: ChatController -> String -> IO JSONString chatSendCmd :: ChatController -> String -> IO JSONString
chatSendCmd cc s = LB.unpack . J.encode . APIResponse Nothing <$> runReaderT (execChatCommand $ B.pack s) cc chatSendCmd cc s = LB.unpack . J.encode . APIResponse Nothing <$> runReaderT (execChatCommand $ B.pack s) cc

View file

@ -3,43 +3,23 @@
module Simplex.Chat.Terminal where module Simplex.Chat.Terminal where
import Control.Logger.Simple
import Control.Monad.Except import Control.Monad.Except
import Control.Monad.Reader
import Simplex.Chat
import Simplex.Chat.Controller import Simplex.Chat.Controller
import Simplex.Chat.Core
import Simplex.Chat.Help (chatWelcome) import Simplex.Chat.Help (chatWelcome)
import Simplex.Chat.Options import Simplex.Chat.Options
import Simplex.Chat.Store
import Simplex.Chat.Terminal.Input import Simplex.Chat.Terminal.Input
import Simplex.Chat.Terminal.Notification import Simplex.Chat.Terminal.Notification
import Simplex.Chat.Terminal.Output import Simplex.Chat.Terminal.Output
import Simplex.Chat.Types (User)
import Simplex.Messaging.Util (raceAny_) import Simplex.Messaging.Util (raceAny_)
import UnliftIO (async, waitEither_)
simplexChat :: WithTerminal t => ChatConfig -> ChatOpts -> t -> IO () simplexChatTerminal :: WithTerminal t => ChatConfig -> ChatOpts -> t -> IO ()
simplexChat cfg@ChatConfig {dbPoolSize, yesToMigrations} opts t simplexChatTerminal cfg opts t = do
| logAgent opts = do sendToast <- initializeNotifications
setLogLevel LogInfo -- LogError simplexChatCore cfg opts (Just sendToast) $ \u cc -> do
withGlobalLogging logCfg initRun ct <- newChatTerminal t
| otherwise = initRun when (firstTime cc) . printToTerminal ct $ chatWelcome u
where runChatTerminal ct cc
initRun = do
sendNotification' <- initializeNotifications
let f = chatStoreFile $ dbFilePrefix opts
st <- createStore f dbPoolSize yesToMigrations
u <- getCreateActiveUser st
ct <- newChatTerminal t
cc <- newChatController st (Just u) cfg opts sendNotification'
runSimplexChat u ct cc
runSimplexChat :: User -> ChatTerminal -> ChatController -> IO ()
runSimplexChat u ct cc = do
when (firstTime cc) . printToTerminal ct $ chatWelcome u
a1 <- async $ runChatTerminal ct cc
a2 <- runReaderT (startChatController u) cc
waitEither_ a1 a2
runChatTerminal :: ChatTerminal -> ChatController -> IO () runChatTerminal :: ChatTerminal -> ChatController -> IO ()
runChatTerminal ct cc = raceAny_ [runTerminalInput ct cc, runTerminalOutput ct cc, runInputLoop ct cc] runChatTerminal ct cc = raceAny_ [runTerminalInput ct cc, runTerminalOutput ct cc, runInputLoop ct cc]

View file

@ -18,6 +18,7 @@ import qualified Data.Text as T
import Network.Socket import Network.Socket
import Simplex.Chat import Simplex.Chat
import Simplex.Chat.Controller (ChatConfig (..), ChatController (..)) import Simplex.Chat.Controller (ChatConfig (..), ChatController (..))
import Simplex.Chat.Core
import Simplex.Chat.Options import Simplex.Chat.Options
import Simplex.Chat.Store import Simplex.Chat.Store
import Simplex.Chat.Terminal import Simplex.Chat.Terminal
@ -46,7 +47,9 @@ opts =
{ dbFilePrefix = undefined, { dbFilePrefix = undefined,
smpServers = ["smp://LcJUMfVhwD8yxjAiSaDzzGF3-kLG4Uh0Fl_ZIjrRwjI=@localhost:5001"], smpServers = ["smp://LcJUMfVhwD8yxjAiSaDzzGF3-kLG4Uh0Fl_ZIjrRwjI=@localhost:5001"],
logConnections = False, logConnections = False,
logAgent = False logAgent = False,
chatCmd = "",
chatCmdDelay = 3
} }
termSettings :: VirtualTerminalSettings termSettings :: VirtualTerminalSettings
@ -83,8 +86,8 @@ virtualSimplexChat dbFilePrefix profile = do
Right user <- runExceptT $ createUser st profile True Right user <- runExceptT $ createUser st profile True
t <- withVirtualTerminal termSettings pure t <- withVirtualTerminal termSettings pure
ct <- newChatTerminal t ct <- newChatTerminal t
cc <- newChatController st (Just user) cfg opts {dbFilePrefix} (const $ pure ()) -- no notifications cc <- newChatController st (Just user) cfg opts {dbFilePrefix} Nothing -- no notifications
chatAsync <- async $ runSimplexChat user ct cc chatAsync <- async . runSimplexChat user cc . const $ runChatTerminal ct
termQ <- newTQueueIO termQ <- newTQueueIO
termAsync <- async $ readTerminalOutput t termQ termAsync <- async $ readTerminalOutput t termQ
pure TestCC {chatController = cc, virtualTerminal = t, chatAsync, termAsync, termQ} pure TestCC {chatController = cc, virtualTerminal = t, chatAsync, termAsync, termQ}