Skip to content

Commit

Permalink
remove from Config.hs all that is currently subsumed by rc-files
Browse files Browse the repository at this point in the history
  • Loading branch information
sorear committed Jan 12, 2007
1 parent a0a49e7 commit 41a6032
Show file tree
Hide file tree
Showing 4 changed files with 45 additions and 57 deletions.
49 changes: 0 additions & 49 deletions Config.hs
Expand Up @@ -3,25 +3,14 @@
--
module Config where

import Message(Nick(Nick))

data Protocol = Irc | Xmpp

-- | The 'Config' type provides configurations for lambdabot. It is used
-- when lambdabot is started to determine the name of lambdabot, what
-- IRC-network lambdabot should join, which channels lambdabot should
-- join upon successful connection, etc.
--
data Config = Config {
name :: Nick, -- ^ The nickname of lambdabot
userinfo :: String, -- ^ The userinfo string for lambdabot
host :: String, -- ^ Host to join
port :: Int, -- ^ The port number to use on the host
protocol :: Protocol, -- ^ either irc or xmpp/jabber
verbose :: Bool, -- ^ Should lambdabot be verbose?
textwidth :: Int, -- ^ How many columns should we use
autojoin :: [Nick], -- ^ List of channels to autojoin
admins :: [Nick], -- ^ List of nicknames that are admins
proxy :: Maybe ([Char], Integer), -- ^ A proxy given as
-- a pair of host and port.

Expand Down Expand Up @@ -53,46 +42,10 @@ data Config = Config {
--
config :: Config
config = Config {
name = nck "lambdabot",
userinfo = "Lambda_Robots:_100%_Loyal",
host = "irc.freenode.net",
protocol = Irc,

port = 6667,
verbose = True,
textwidth = 350,
proxy = Nothing, -- Just ("www-proxy",3128),

autojoin = [nck "#haskell"
,nck "#haskell-blah"
,nck "#haskell-overflow"
,nck "#haskell.hac07"
{- ,nck "#haskell.de"
,nck "#haskell.es"
,nck "#haskell.fi"
,nck "#haskell.fr"
,nck "#haskell.hr"
,nck "#haskell.it"
,nck "#haskell.jp"
,nck "#haskell.no"
,nck "#haskell.se" -}
,nck "#gentoo-haskell"
,nck "#gentoo-uy"
,nck "#ghc"
,nck "#darcs"
,nck "#oasis"
,nck "#perl6"
,nck "#jtiger"
,nck "#unicycling"
,nck "#ScannedInAvian"],

admins = map nck [
"Pseudonym", "shapr", "vincenz", "Igloo",
"Cale", "dons", "TheHunter", "musasabi",
"Lemmih", "sjanssen", "sorear", "int-e"

],

fortunePath = "/home/dons/fortune/",
fptoolsPath = "/home/dons/fptools",

Expand All @@ -105,5 +58,3 @@ config = Config {
disabledCommands = ["listchans", "slap", "echo", "remember", "state"]

}
where nck = Nick "freenode"

12 changes: 6 additions & 6 deletions Lambdabot.hs
Expand Up @@ -36,7 +36,6 @@ module Lambdabot (

import qualified Message as Msg
import qualified Shared as S
import qualified Config (config, name, admins)
import qualified IRCBase as IRC (IrcMessage, quit, privmsg)

import Lib.Signals
Expand Down Expand Up @@ -253,7 +252,7 @@ runIrc evcmds initialise ld plugins = withSocketsDo $ do
rost <- initRoState
r <- try $ evalLB (do withDebug "Initialising plugins" initialise
withIrcSignalCatch mainLoop)
rost (initState (Config.admins Config.config) ld plugins evcmds)
rost (initState ld plugins evcmds)

-- clean up and go home
case r of
Expand All @@ -280,9 +279,9 @@ initRoState = do
--
-- | Default rw state
--
initState :: [Msg.Nick] -> S.DynLoad -> [String] -> [String] -> IRCRWState
initState as ld plugins evcmds = IRCRWState {
ircPrivilegedUsers = M.fromList $ zip (Msg.Nick "offlinerc" "null" : as) (repeat True),
initState :: S.DynLoad -> [String] -> [String] -> IRCRWState
initState ld plugins evcmds = IRCRWState {
ircPrivilegedUsers = M.singleton (Msg.Nick "offlinerc" "null") True,
ircChannels = M.empty,
ircModules = M.empty,
ircServerMap = M.empty,
Expand Down Expand Up @@ -717,7 +716,8 @@ mlines = (mbreak =<<) . lines
-- | Don't send any output to alleged bots.
checkRecip :: OutputFilter
checkRecip who msg
| who == Config.name Config.config = return []
-- FIXME: this doesn't work with plugin protocols :(
-- | who == Config.name Config.config = return []
| "bot" `isSuffixOf` lowerCaseString (Msg.nName who) = return []
| otherwise = return msg

Expand Down
4 changes: 2 additions & 2 deletions Plugin/Base.hs
Expand Up @@ -7,7 +7,7 @@ import Plugin

import IRCBase (IrcMessage, timeReply, errShowMsg)
-- import Message (getTopic, nick, joinChannel, body, fullName, channels)
import Message (getTopic, nick, joinChannel, server, body, Nick(..), lambdabotName, showNick, readNick)
import Message (getTopic, nick, server, body, Nick(..), lambdabotName, showNick, readNick)

import qualified Data.Map as M (insert, delete)

Expand Down Expand Up @@ -127,7 +127,7 @@ doTOPIC msg
put (s { ircChannels = M.insert (mkCN loc) (tail $ head $ tail $ body msg) (ircChannels s)})

doRPL_WELCOME :: Callback
doRPL_WELCOME _msg = mapM_ (send . joinChannel) (autojoin config)
doRPL_WELCOME = doIGNORE

doQUIT :: Callback
doQUIT msg = doIGNORE msg
Expand Down
37 changes: 37 additions & 0 deletions online.rc
@@ -0,0 +1,37 @@
irc-connect freenode chat.freenode.net 6667 lambdabot Lambda_Robots:_100%_Loyal
join freenode:#haskell
join freenode:#haskell
join freenode:#haskell-blah
join freenode:#haskell-overflow
join freenode:#haskell.hac07
join freenode:#haskell.de
join freenode:#haskell.es
join freenode:#haskell.fi
join freenode:#haskell.fr
join freenode:#haskell.hr
join freenode:#haskell.it
join freenode:#haskell.jp
join freenode:#haskell.no
join freenode:#haskell.se
join freenode:#gentoo-haskell
join freenode:#gentoo-uy
join freenode:#ghc
join freenode:#darcs
join freenode:#oasis
join freenode:#perl6
join freenode:#jtiger
join freenode:#unicycling
join freenode:#ScannedInAvian
admin + Pseudonym
admin + shapr
admin + vincenz
admin + Igloo
admin + Cale
admin + dons
admin + TheHunter
admin + musasabi
admin + Lemmih
admin + sjanssen
admin + sorear
admin + int-e
source passwd.rc

0 comments on commit 41a6032

Please sign in to comment.