Continue refactoring, worked on the core loop and the plugin infrastructure.
This commit is contained in:
parent
ff07633fb8
commit
d4be110200
7 changed files with 140 additions and 38 deletions
|
@ -6,10 +6,13 @@ module Hsbot.Config
|
||||||
, noSSL
|
, noSSL
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Control.Concurrent.Chan
|
||||||
import Network
|
import Network
|
||||||
|
import qualified Network.IRC as IRC
|
||||||
import Network.TLS
|
import Network.TLS
|
||||||
import Network.TLS.Extra
|
import Network.TLS.Extra
|
||||||
|
|
||||||
|
import Hsbot.Message
|
||||||
data Config = Config
|
data Config = Config
|
||||||
{ configErrors :: Maybe String
|
{ configErrors :: Maybe String
|
||||||
, configTLS :: TLSConfig
|
, configTLS :: TLSConfig
|
||||||
|
@ -18,7 +21,7 @@ data Config = Config
|
||||||
, configChannels :: [String]
|
, configChannels :: [String]
|
||||||
, configNicknames :: [String]
|
, configNicknames :: [String]
|
||||||
, configRealname :: String
|
, configRealname :: String
|
||||||
, configPlugins :: [String]
|
, configPlugins :: [(String, Chan Message -> Chan Message -> IO ())]
|
||||||
}
|
}
|
||||||
|
|
||||||
defaultConfig :: Config
|
defaultConfig :: Config
|
||||||
|
@ -30,7 +33,7 @@ defaultConfig = Config
|
||||||
, configChannels = ["#hsbot"]
|
, configChannels = ["#hsbot"]
|
||||||
, configNicknames = ["hsbot"]
|
, configNicknames = ["hsbot"]
|
||||||
, configRealname = "The One True bot, with it's haskell soul."
|
, configRealname = "The One True bot, with it's haskell soul."
|
||||||
, configPlugins = ["Ping", "Core"] }
|
, configPlugins = [] }
|
||||||
|
|
||||||
data TLSConfig = TLSConfig
|
data TLSConfig = TLSConfig
|
||||||
{ sslOn :: Bool
|
{ sslOn :: Bool
|
||||||
|
|
|
@ -7,8 +7,10 @@ module Hsbot.Core
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
import Control.Exception (IOException, catch)
|
import Control.Exception (IOException, catch)
|
||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
|
import Control.Monad.State
|
||||||
import qualified Data.ByteString.Char8 as C
|
import qualified Data.ByteString.Char8 as C
|
||||||
import qualified Data.ByteString.Lazy as L
|
import qualified Data.ByteString.Lazy as L
|
||||||
|
import qualified Data.Map as M
|
||||||
import Network
|
import Network
|
||||||
import qualified Network.IRC as IRC
|
import qualified Network.IRC as IRC
|
||||||
import Network.BSD (getHostName)
|
import Network.BSD (getHostName)
|
||||||
|
@ -51,31 +53,43 @@ initHsbot config = do
|
||||||
|
|
||||||
runHsbot :: Env IO (BotStatus)
|
runHsbot :: Env IO (BotStatus)
|
||||||
runHsbot = do
|
runHsbot = do
|
||||||
|
let bot = BotState { botPlugins = M.empty
|
||||||
|
, botHooks = []
|
||||||
|
, botChannels = []
|
||||||
|
, botNickname = [] }
|
||||||
|
evalStateT trueRunHsbot bot
|
||||||
|
where
|
||||||
|
trueRunHsbot :: Bot (Env IO) (BotStatus)
|
||||||
|
trueRunHsbot = do
|
||||||
-- First we say hello
|
-- First we say hello
|
||||||
env <- ask
|
env <- lift ask
|
||||||
hostname <- liftIO getHostName
|
hostname <- liftIO getHostName
|
||||||
let connhdl = envHandle env
|
let connhdl = envHandle env
|
||||||
tlsCtx = envTLSCtx env
|
tlsCtx = envTLSCtx env
|
||||||
config = envConfig env
|
config = envConfig env
|
||||||
nickname = head $ configNicknames config
|
nickname = head $ configNicknames config
|
||||||
channels = configChannels config
|
channels = configChannels config
|
||||||
liftIO . sendStrToClient connhdl tlsCtx . IRC.encode $ IRC.nick nickname
|
liftIO . sendStr connhdl tlsCtx . IRC.encode $ IRC.nick nickname
|
||||||
liftIO . sendStrToClient connhdl tlsCtx . IRC.encode $ IRC.user nickname hostname "*" (configRealname config)
|
liftIO . sendStr connhdl tlsCtx . IRC.encode $ IRC.user nickname hostname "*" (configRealname config)
|
||||||
mapM_ (liftIO . sendStrToClient connhdl tlsCtx . IRC.encode . IRC.joinChan) channels
|
mapM_ (liftIO . sendStr connhdl tlsCtx . IRC.encode . IRC.joinChan) channels
|
||||||
-- Next we spawn the reader thread
|
-- Next we spawn the reader thread
|
||||||
liftIO $ debugM "Hsbot.Core" $ "Spawning reader thread"
|
liftIO $ debugM "Hsbot.Core" $ "Spawning reader thread"
|
||||||
myOwnThreadId <- liftIO $ myThreadId
|
myOwnThreadId <- liftIO $ myThreadId
|
||||||
chan <- asks envChan
|
chan <- lift $ asks envChan
|
||||||
(liftIO . forkIO $ botReader connhdl tlsCtx chan myOwnThreadId) >>= addThreadIdToQuitMVar
|
(liftIO . forkIO $ botReader connhdl tlsCtx chan myOwnThreadId) >>= lift . addThreadIdToQuitMVar
|
||||||
-- Then we spawn all plugins
|
-- Then we spawn all plugins
|
||||||
-- asks envSocket >>= mapM_ ( ----- what's next? the core server handling! ----- )
|
-- asks envSocket >>= mapM_ ( ----- what's next? the core server handling! ----- )
|
||||||
-- Finally we spawn the main bot loop
|
-- Finally we spawn the main bot loop
|
||||||
--
|
bot <- get
|
||||||
|
finalStateMVar <- liftIO newEmptyMVar
|
||||||
|
(liftIO . forkIO $ runReaderT (execStateT botLoop bot >>= storeFinalState finalStateMVar) env) >>= lift . addThreadIdToQuitMVar
|
||||||
-- We wait for the quit signal
|
-- We wait for the quit signal
|
||||||
code <- asks envQuitMv >>= liftIO . takeMVar
|
code <- asks envQuitMv >>= liftIO . takeMVar
|
||||||
-- and we clean things up
|
-- and we clean things up
|
||||||
asks envThreadIdsMv >>= liftIO . readMVar >>= liftIO . mapM_ killThread
|
asks envThreadIdsMv >>= liftIO . readMVar >>= liftIO . mapM_ killThread
|
||||||
return code
|
return code
|
||||||
|
storeFinalState :: MVar BotState -> BotState -> Env IO ()
|
||||||
|
storeFinalState finalStateMVar finalState = liftIO $ putMVar finalStateMVar finalState
|
||||||
|
|
||||||
botReader :: Handle -> Maybe TLSCtx -> Chan Message -> ThreadId -> IO ()
|
botReader :: Handle -> Maybe TLSCtx -> Chan Message -> ThreadId -> IO ()
|
||||||
botReader _ (Just ctx) chan _ = forever $
|
botReader _ (Just ctx) chan _ = forever $
|
||||||
|
@ -90,6 +104,20 @@ botReader handle Nothing chan fatherThreadId = forever $
|
||||||
killThread myId
|
killThread myId
|
||||||
return ""
|
return ""
|
||||||
|
|
||||||
|
botLoop :: Bot (Env IO) ()
|
||||||
|
botLoop = do
|
||||||
|
chan <- lift $ asks envChan
|
||||||
|
hooks <- gets botHooks
|
||||||
|
msg <- liftIO $ readChan chan
|
||||||
|
mapM_ (liftIO . flip writeChan msg) hooks
|
||||||
|
case msg of
|
||||||
|
IncomingMsg _ -> return () -- TODO parse for core commands
|
||||||
|
OutgoingMsg outMsg -> do
|
||||||
|
env <- lift ask
|
||||||
|
let connhdl = envHandle env
|
||||||
|
tlsCtx = envTLSCtx env
|
||||||
|
liftIO . sendStr connhdl tlsCtx $ IRC.encode outMsg
|
||||||
|
|
||||||
handleIncomingStr :: Chan Message -> String -> IO ()
|
handleIncomingStr :: Chan Message -> String -> IO ()
|
||||||
handleIncomingStr chan str = do
|
handleIncomingStr chan str = do
|
||||||
case IRC.decode str of
|
case IRC.decode str of
|
||||||
|
|
9
Hsbot/Message.hs
Normal file
9
Hsbot/Message.hs
Normal file
|
@ -0,0 +1,9 @@
|
||||||
|
module Hsbot.Message
|
||||||
|
( Message (..)
|
||||||
|
) where
|
||||||
|
|
||||||
|
import qualified Network.IRC as IRC
|
||||||
|
|
||||||
|
data Message = IncomingMsg IRC.Message
|
||||||
|
| OutgoingMsg IRC.Message
|
||||||
|
|
38
Hsbot/Plugin/Ping.hs
Normal file
38
Hsbot/Plugin/Ping.hs
Normal file
|
@ -0,0 +1,38 @@
|
||||||
|
module Hsbot.Plugin.Ping
|
||||||
|
( pingId
|
||||||
|
, ping
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Control.Concurrent.Chan ()
|
||||||
|
import Control.Exception
|
||||||
|
import Control.Monad.State (execStateT, forever)
|
||||||
|
import qualified Network.IRC as IRC
|
||||||
|
import Prelude hiding (catch)
|
||||||
|
|
||||||
|
import Hsbot.Message
|
||||||
|
import Hsbot.Types
|
||||||
|
import Hsbot.Utils
|
||||||
|
|
||||||
|
pingId :: PluginId
|
||||||
|
pingId = PluginId
|
||||||
|
{ pluginName = "ping"
|
||||||
|
, pluginEp = ping }
|
||||||
|
|
||||||
|
-- | The plugin's main entry point
|
||||||
|
ping :: PluginState -> IO ()
|
||||||
|
ping state = do
|
||||||
|
_ <- (execStateT run state) `catch` (\(_ :: AsyncException) -> return state)
|
||||||
|
return ()
|
||||||
|
|
||||||
|
-- | The IrcPlugin monad main function
|
||||||
|
run :: Plugin IO ()
|
||||||
|
run = forever $ do
|
||||||
|
msg <- readMsg
|
||||||
|
eval msg
|
||||||
|
where
|
||||||
|
eval :: Message -> Plugin IO ()
|
||||||
|
eval (IncomingMsg msg)
|
||||||
|
| (IRC.msg_command msg) == "PING" = writeMsg . OutgoingMsg . IRC.Message Nothing "PONG" $ IRC.msg_params msg
|
||||||
|
| otherwise = return ()
|
||||||
|
eval _ = return ()
|
||||||
|
|
|
@ -5,6 +5,8 @@ module Hsbot.Types
|
||||||
, BotEnv (..)
|
, BotEnv (..)
|
||||||
, Env
|
, Env
|
||||||
, Message (..)
|
, Message (..)
|
||||||
|
, Plugin
|
||||||
|
, PluginId (..)
|
||||||
, PluginState (..)
|
, PluginState (..)
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
@ -12,11 +14,11 @@ import Control.Concurrent
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
import qualified Network.IRC as IRC
|
|
||||||
import Network.TLS
|
import Network.TLS
|
||||||
import System.IO
|
import System.IO
|
||||||
|
|
||||||
import Hsbot.Config
|
import Hsbot.Config
|
||||||
|
import Hsbot.Message
|
||||||
|
|
||||||
-- The bot environment
|
-- The bot environment
|
||||||
type Env = ReaderT BotEnv
|
type Env = ReaderT BotEnv
|
||||||
|
@ -36,19 +38,24 @@ type Bot = StateT BotState
|
||||||
|
|
||||||
data BotState = BotState
|
data BotState = BotState
|
||||||
{ botPlugins :: M.Map String (PluginState, MVar (), ThreadId)
|
{ botPlugins :: M.Map String (PluginState, MVar (), ThreadId)
|
||||||
, botCommands :: M.Map String [String]
|
, botHooks :: [Chan Message]
|
||||||
, botChannels :: [String]
|
, botChannels :: [String]
|
||||||
, botNickname :: String
|
, botNickname :: String
|
||||||
}
|
}
|
||||||
|
|
||||||
-- The Plugin monad
|
-- The Plugin monad
|
||||||
|
type Plugin = StateT PluginState
|
||||||
|
|
||||||
data PluginState = PluginState
|
data PluginState = PluginState
|
||||||
{ pluginName :: String
|
{ pluginId :: PluginId
|
||||||
, pluginChan :: Chan Message
|
, pluginChan :: Chan Message
|
||||||
|
, pluginMaster :: Chan Message
|
||||||
|
}
|
||||||
|
|
||||||
|
data PluginId = PluginId
|
||||||
|
{ pluginName :: String
|
||||||
|
, pluginEp :: PluginState -> IO ()
|
||||||
}
|
}
|
||||||
|
|
||||||
data BotStatus = BotContinue | BotExit | BotReload | BotRestart deriving (Show)
|
data BotStatus = BotContinue | BotExit | BotReload | BotRestart deriving (Show)
|
||||||
|
|
||||||
data Message = IncomingMsg IRC.Message
|
|
||||||
| OutgoingMsg IRC.Message
|
|
||||||
|
|
||||||
|
|
|
@ -4,13 +4,16 @@ module Hsbot.Utils
|
||||||
, first
|
, first
|
||||||
, initTLSEnv
|
, initTLSEnv
|
||||||
, readCertificate
|
, readCertificate
|
||||||
|
, readMsg
|
||||||
, readPrivateKey
|
, readPrivateKey
|
||||||
, sendStrToClient
|
, sendStr
|
||||||
, setGlobalQuitMVar
|
, setGlobalQuitMVar
|
||||||
|
, writeMsg
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
|
import Control.Monad.State
|
||||||
import qualified Crypto.Cipher.RSA as RSA
|
import qualified Crypto.Cipher.RSA as RSA
|
||||||
import qualified Data.ByteString as B
|
import qualified Data.ByteString as B
|
||||||
import qualified Data.ByteString.Char8 as C
|
import qualified Data.ByteString.Char8 as C
|
||||||
|
@ -23,6 +26,7 @@ import Network.TLS
|
||||||
import System.IO
|
import System.IO
|
||||||
|
|
||||||
import Hsbot.Config
|
import Hsbot.Config
|
||||||
|
import Hsbot.Message
|
||||||
import Hsbot.Types
|
import Hsbot.Types
|
||||||
|
|
||||||
-- utility functions
|
-- utility functions
|
||||||
|
@ -45,9 +49,20 @@ first :: (a, b, c) -> a
|
||||||
first (a, _, _) = a
|
first (a, _, _) = a
|
||||||
|
|
||||||
-- Helpers
|
-- Helpers
|
||||||
sendStrToClient :: Handle -> Maybe TLSCtx -> String -> IO ()
|
sendStr :: Handle -> Maybe TLSCtx -> String -> IO ()
|
||||||
sendStrToClient _ (Just ctx) msg = sendData ctx $ L.fromChunks [C.pack msg]
|
sendStr _ (Just ctx) msg = sendData ctx $ L.fromChunks [C.pack msg]
|
||||||
sendStrToClient handle Nothing msg = hPutStrLn handle msg
|
sendStr handle Nothing msg = hPutStrLn handle msg
|
||||||
|
|
||||||
|
-- Plugin Utils
|
||||||
|
readMsg :: Plugin IO (Message)
|
||||||
|
readMsg = do
|
||||||
|
chan <- gets pluginChan
|
||||||
|
liftIO $ readChan chan >>= return
|
||||||
|
|
||||||
|
writeMsg :: Message -> Plugin IO ()
|
||||||
|
writeMsg msg = do
|
||||||
|
chan <- gets pluginMaster
|
||||||
|
liftIO $ writeChan chan msg
|
||||||
|
|
||||||
-- TLS utils
|
-- TLS utils
|
||||||
initTLSEnv :: TLSConfig -> IO (TLSParams)
|
initTLSEnv :: TLSConfig -> IO (TLSParams)
|
||||||
|
|
|
@ -1,5 +1,5 @@
|
||||||
Name: hsbot
|
Name: hsbot
|
||||||
Version: 0.4
|
Version: 0.4.1
|
||||||
Cabal-version: >=1.2
|
Cabal-version: >=1.2
|
||||||
Synopsis: A multipurposes IRC bot
|
Synopsis: A multipurposes IRC bot
|
||||||
Description:
|
Description:
|
||||||
|
@ -22,7 +22,9 @@ Library
|
||||||
--Hsbot.Command
|
--Hsbot.Command
|
||||||
Hsbot.Config
|
Hsbot.Config
|
||||||
Hsbot.Core
|
Hsbot.Core
|
||||||
|
Hsbot.Message
|
||||||
--Hsbot.Plugin
|
--Hsbot.Plugin
|
||||||
|
Hsbot.Plugin.Ping
|
||||||
Hsbot.Types
|
Hsbot.Types
|
||||||
Hsbot.Utils
|
Hsbot.Utils
|
||||||
Extensions: DeriveDataTypeable FlexibleContexts ScopedTypeVariables
|
Extensions: DeriveDataTypeable FlexibleContexts ScopedTypeVariables
|
||||||
|
|
Reference in a new issue