hexchat-0.0.2.0: Haskell scripting interface for HexChat

Copyright(C) 2017 mniip
LicenseMIT
Maintainermniip@mniip.com
Stabilitynone
Portabilitynone
Safe HaskellNone
LanguageHaskell2010

HexChat

Contents

Description

A HexChat script is a .hs file that defines a global identifier info with type ModInfo. This structure contains the necessary metadata about a script as well its initialization and deinitialization functions. From your initialization function you may want to hook some events. Any remaining hooks are automatically unhooked after the deinitializer so you don't have to worry about that.

Synopsis

Module Info

data ModInfo a Source #

This datatype contains metadata about the script. Every script should define an global binding named info of this type. This structure contains internal fields necessary for scripting to work, so when constructing an object please use the default value modInfo with record modification notation, like this:

info = modInfo { modName = "a module", modAuthor = "somepony", ... }

The type parameter signifies the return type of the initializer and has no special meaning otherwise, you can specialize it to anything you want.

If you need to pass a lot of data to the deinitializer you could simply let a ~ IO () and modDeinit = id, such as in the following:

info = modInfo
    { modInit = do
          x <- createX
          return $ do
              destroyX x
    , modDeinit = id
    }

Constructors

ModInfo 

Fields

  • modName :: String

    Name of the script.

  • modVersion :: String

    Version of the script.

  • modAuthor :: String

    Author of the script.

  • modDescription :: String

    A short description of the script that can fit in the "Plugins and Scripts" list window.

  • modInit :: IO a

    This is the entry point of the script. It will be executed immediately after the script is compiled and loaded. The returned value will be opaquely passed to modDeinit.

  • modDeinit :: a -> IO ()

    This function will be executed shortly before the script is unloaded. You can place any cleanup routines here. As argument it receives whatever modInit returned.

  • modStaticData :: StaticData

    An internal field that lets the different (to the linker) instances of the HexChat library identify eachother. Please inherit the value of this field from modInfo.

modInfo :: ModInfo a Source #

A default value for ModInfo. This has some sensible defaults and also provides the values of internal fields necessary for the operation of the interface.

Interfacing HexChat

command :: String -> IO () Source #

Invoke a HexChat command as if the user has typed it in the inputbox. Do not include the leading /.

print :: String -> IO () Source #

Print some text to the buffer.

emitPrint :: String -> [String] -> IO Bool Source #

Output a Text Event to the buffer. First argument is the Text Event identifier (see Settings -> Text Events), second is the list of event's parameters.

emitPrintAttrs :: EventAttrs -> String -> [String] -> IO Bool Source #

Same as emitPrint but also lets you specify Event Attributes for the event.

sendModes :: [String] -> Int -> Char -> Char -> IO () Source #

sendModes targets n sign mode where sign is + or - and mode is a channel mode character will set the specified channel mode on each of the specified targets, sending n modes per line, or the server's advertised maximum if n is zero.

nickCmp :: String -> String -> IO Ordering Source #

Compare two nicknames according to the rules of the server.

strip :: Bool -> Bool -> String -> IO String Source #

strip colors format will strip colors if colors is True, and miscellaneous formatting if formatting is True, from the provided string.

getPrefs :: String -> (String -> IO a) -> (Int -> IO a) -> (Bool -> IO a) -> IO (Maybe a) Source #

Get a HexChat preference value (see /set). You should pass 3 continuations one of which will be invoked depending on the type of the actual preference. Returns Nothing if no preference with that name exists.

getPrefString :: String -> IO (Maybe String) Source #

Return the value of a preference that is supposedly a String. Returns Nothing if no such preference exists or it is of the wrong type.

getPrefInt :: String -> IO (Maybe Int) Source #

Return the value of a preference that is supposedly an Int. Returns Nothing if no such preference exists or it is of the wrong type.

getPrefBool :: String -> IO (Maybe Bool) Source #

Return the value of a preference that is supposedly a Bool. Returns Nothing if no such preference exists or it is of the wrong type.

data List Source #

Instances

Eq List Source # 

Methods

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

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

Hooks

All hooks have a priority that determines the order in which HexChat invokes them. Each hook can also affect the propagation of the event to other hooks.

data Eat Source #

This type defines whether the current hook "consumes" the event or lets other hooks know about it.

Constructors

EatNone

Pass the event to everything else.

EatHexChat

Pass the event to all other scripts but not HexChat.

EatPlugin

Pass the event to HexChat but not any other scripts.

EatAll

Completely consume the event.

Instances

data Hook Source #

An opaque type referencing a particular hook. Can be passed to unhook.

Instances

Eq Hook Source # 

Methods

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

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

Ord Hook Source # 

Methods

compare :: Hook -> Hook -> Ordering #

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

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

(>) :: Hook -> Hook -> Bool #

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

max :: Hook -> Hook -> Hook #

min :: Hook -> Hook -> Hook #

Show Hook Source # 

Methods

showsPrec :: Int -> Hook -> ShowS #

show :: Hook -> String #

showList :: [Hook] -> ShowS #

hookCommand :: String -> CInt -> String -> ([String] -> [String] -> IO Eat) -> IO Hook Source #

hookCommand cmd priority description f registers a command named cmd (with description description). The given f will be passed a list of command's arguments (proper words) and a list of "leftovers" for every position in the word list (with the exact original whitespace).

If cmd is "" then instead the hook will be invoked whenever the user types anything not beginning with /.

hookPrint :: String -> CInt -> ([String] -> IO Eat) -> IO Hook Source #

hookPrint event priority f hooks f to be invoked whenever a Text Event event is to be displayed on screen. The given f will be passed a list of event's parameters.

hookPrintAttrs :: String -> CInt -> ([String] -> EventAttrs -> IO Eat) -> IO Hook Source #

hookPrintAttrs event priority f hooks f to be invoked whenever a Text Event event is to be displayed on screen. The given f will be passed a list of event's parameters, and the attributes.

hookServer :: String -> CInt -> ([String] -> [String] -> IO Eat) -> IO Hook Source #

hookServer word priority f hooks f to be invoked whenever a word command arrives from the IRC server. The given f will be passed a list of command's arguments (proper words) and a list of "leftovers" for every position in the word list (with the exact original whitespace). Processing of : long arguments is *NOT* done.

If cmd is "RAW LINE" then the hook will be invoked for all commands received from the server.

hookServerAttrs :: String -> CInt -> ([String] -> [String] -> EventAttrs -> IO Eat) -> IO Hook Source #

hookServer word priority f hooks f to be invoked whenever a word command arrives from the IRC server. The given f will be passed a list of command's arguments (proper words), a list of "leftovers" for every position in the word list (with the exact original whitespace), and the event attributes. Processing of : long arguments is *NOT* done.

If cmd is "RAW LINE" then the hook will be invoked for all commands received from the server.

unhook :: Hook -> IO () Source #

Remove the given hook. All hooks are automatically removed when the script is unloaded.

Contexts

Some HexChat interface functions are specific to a given Context, which corresponds to a tab or window. By default whenever a hook is invoked it is running in the event's relevant context. If you need to output text or commands to a different tab you should change the context.

data Context Source #

An opaque type referencing a context (tab or window).

findContext :: Maybe String -> Maybe String -> IO (Maybe Context) Source #

findContext mserver mtabname finds the context corresponding to the given tab name (or to the front tab if Nothing) in the given server (or in any of the servers if Nothing).

getContext :: IO Context Source #

Obtains the current context.

setContext :: Context -> IO Bool Source #

Sets the current context. The scope of this function is limited to the currently executing hook (or the initializer/deinitializer).

withContext :: Context -> IO a -> IO a Source #

Execute a given IO action in a given context a-la bracket.