ircbot-0.6.5.3: A library for writing IRC bots

Safe HaskellNone
LanguageHaskell2010

Network.IRC.Bot.Core

Synopsis

Documentation

simpleBot Source #

Arguments

:: BotConf

Bot configuration

-> [BotPartT IO ()]

bot parts (must include pingPart, or equivalent)

-> IO ([ThreadId], IO ())

ThreadId for all forked handler threads and a function that forces a reconnect

simpleBot connects to the server and handles messages using the supplied BotPartTs

the 'Chan Message' for the optional logging function will include all received and sent messages. This means that the bots output will be included in the logs.

simpleBot' Source #

Arguments

:: Maybe (Chan Message -> IO ())

optional logging function

-> Logger

application logging

-> Maybe (Int, Int)

rate limiter settings (burst length, delay in microseconds)

-> HostName

irc server to connect

-> PortID

irc port to connect to (usually, 'PortNumber 6667')

-> ByteString

irc nick

-> String

command prefix

-> User

irc user info

-> [BotPartT IO ()]

bot parts (must include pingPart, channelsPart, and 'nickUserPart)'

-> IO ([ThreadId], IO ())

ThreadId for all forked handler threads and an IO action that forces a reconnect

simpleBot' connects to the server and handles messages using the supplied BotPartTs

the 'Chan Message' for the optional logging function will include all received and sent messages. This means that the bots output will be included in the logs.

data BotConf Source #

Bot configuration

Constructors

BotConf 

Fields

data User Source #

Constructors

User 

Fields

Instances

Eq User Source # 

Methods

(==) :: User -> User -> Bool #

(/=) :: User -> User -> Bool #

Data User Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> User -> c User #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c User #

toConstr :: User -> Constr #

dataTypeOf :: User -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c User) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c User) #

gmapT :: (forall b. Data b => b -> b) -> User -> User #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> User -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> User -> r #

gmapQ :: (forall d. Data d => d -> u) -> User -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> User -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> User -> m User #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> User -> m User #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> User -> m User #

Ord User Source # 

Methods

compare :: User -> User -> Ordering #

(<) :: User -> User -> Bool #

(<=) :: User -> User -> Bool #

(>) :: User -> User -> Bool #

(>=) :: User -> User -> Bool #

max :: User -> User -> User #

min :: User -> User -> User #

Read User Source # 
Show User Source # 

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #