Archived
1
0
Fork 0

Added access controls to hsbot.

This commit is contained in:
Julien Dessaux 2011-08-08 11:39:41 +02:00
parent e74094d5d9
commit 1c8cab09cb
5 changed files with 32 additions and 6 deletions

View file

@ -16,6 +16,7 @@ defaultConfig = Config
, configTLS = noSSL , configTLS = noSSL
, configAddress = "localhost" , configAddress = "localhost"
, configPort = PortNumber 6667 , configPort = PortNumber 6667
, configAccess = []
, 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."

View file

@ -76,6 +76,7 @@ runHsbot = do
mapM_ (liftIO . sendStr connhdl tlsCtx . IRC.encode . IRC.joinChan) channels mapM_ (liftIO . sendStr connhdl tlsCtx . IRC.encode . IRC.joinChan) channels
-- Finally we set the new bot state -- Finally we set the new bot state
asks envBotState >>= liftIO . flip putMVar BotState { botPlugins = M.empty asks envBotState >>= liftIO . flip putMVar BotState { botPlugins = M.empty
, botAccess = configAccess config
, botHooks = [] , botHooks = []
, botChannels = channels , botChannels = channels
, botNickname = nickname } , botNickname = nickname }

View file

@ -1,5 +1,7 @@
module Hsbot.Types module Hsbot.Types
( Bot ( AccessList (..)
, AccessRight (..)
, Bot
, BotState (..) , BotState (..)
, BotStatus (..) , BotStatus (..)
, BotEnv (..) , BotEnv (..)
@ -40,6 +42,7 @@ type Bot = StateT BotState
data BotState = BotState data BotState = BotState
{ botPlugins :: M.Map String (PluginEnv, ThreadId) { botPlugins :: M.Map String (PluginEnv, ThreadId)
, botAccess :: [AccessList]
, botHooks :: [Chan Message] , botHooks :: [Chan Message]
, botChannels :: [String] , botChannels :: [String]
, botNickname :: String , botNickname :: String
@ -71,12 +74,20 @@ data Config = Config
, configTLS :: TLSConfig , configTLS :: TLSConfig
, configAddress :: String , configAddress :: String
, configPort :: PortID , configPort :: PortID
, configAccess :: [AccessList]
, configChannels :: [String] , configChannels :: [String]
, configNicknames :: [String] , configNicknames :: [String]
, configRealname :: String , configRealname :: String
, configPlugins :: [PluginId] , configPlugins :: [PluginId]
} }
data AccessRight = Admin | JoinPart | Kick | Say deriving (Eq, Show)
data AccessList = AccessList
{ accessMask :: IRC.Prefix
, accessList :: [AccessRight]
} deriving (Show)
data TLSConfig = TLSConfig data TLSConfig = TLSConfig
{ sslOn :: Bool { sslOn :: Bool
, sslVersions :: [Network.TLS.Version] , sslVersions :: [Network.TLS.Version]

View file

@ -1,6 +1,7 @@
module Hsbot.Utils module Hsbot.Utils
( addThreadIdToQuitMVar ( addThreadIdToQuitMVar
, delThreadIdFromQuitMVar , delThreadIdFromQuitMVar
, hasAccess
, initTLSEnv , initTLSEnv
, sendStr , sendStr
, setGlobalQuitMVar , setGlobalQuitMVar
@ -8,8 +9,10 @@ module Hsbot.Utils
import Control.Concurrent import Control.Concurrent
import Control.Monad.Reader import Control.Monad.Reader
import Control.Monad.State
import qualified Data.ByteString.Lazy.UTF8 as L import qualified Data.ByteString.Lazy.UTF8 as L
import Data.List import qualified Data.List as L
import qualified Network.IRC as IRC
import Network.TLS import Network.TLS
import System.IO import System.IO
@ -24,13 +27,25 @@ addThreadIdToQuitMVar thrId = do
delThreadIdFromQuitMVar :: ThreadId -> Env IO () delThreadIdFromQuitMVar :: ThreadId -> Env IO ()
delThreadIdFromQuitMVar thrId = do delThreadIdFromQuitMVar thrId = do
threadIdsMv <- asks envThreadIdsMv threadIdsMv <- asks envThreadIdsMv
liftIO $ modifyMVar_ threadIdsMv (return . delete thrId) liftIO $ modifyMVar_ threadIdsMv (return . L.delete thrId)
setGlobalQuitMVar :: BotStatus -> Env IO () setGlobalQuitMVar :: BotStatus -> Env IO ()
setGlobalQuitMVar status = do setGlobalQuitMVar status = do
quitMv <- asks envQuitMv quitMv <- asks envQuitMv
liftIO $ putMVar quitMv status liftIO $ putMVar quitMv status
-- Access rights
hasAccess :: Maybe IRC.Prefix -> AccessRight -> Env IO (Bool)
hasAccess Nothing _ = return False
hasAccess (Just mask) right = do
botMVar <- asks envBotState
liftIO (readMVar botMVar) >>= evalStateT (gets botAccess >>= return . or . map accessMatch)
where
accessMatch :: AccessList -> Bool
accessMatch (AccessList amask arights)
| mask == amask = or [L.elem Admin arights, L.elem right arights]
| otherwise = False
-- Helpers -- Helpers
sendStr :: Handle -> Maybe TLSCtx -> String -> IO () sendStr :: Handle -> Maybe TLSCtx -> String -> IO ()
sendStr _ (Just ctx) msg = sendData ctx . L.fromString $ msg ++ "\r\n" sendStr _ (Just ctx) msg = sendData ctx . L.fromString $ msg ++ "\r\n"

4
TODO
View file

@ -1,8 +1,6 @@
* add admin rights
* add the hability to manage rights for plugins, as quote editing
* better hooks? * better hooks?
* add help MVar * add help MVar
* add regexes support in accessList prefix