Copyright | (C) 2017 mniip |
---|---|
License | MIT |
Maintainer | mniip@mniip.com |
Stability | none |
Portability | none |
Safe Haskell | None |
Language | Haskell2010 |
HexChat
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.
- data ModInfo a = ModInfo {
- modName :: String
- modVersion :: String
- modAuthor :: String
- modDescription :: String
- modInit :: IO a
- modDeinit :: a -> IO ()
- modStaticData :: StaticData
- modInfo :: ModInfo a
- command :: String -> IO ()
- print :: String -> IO ()
- emitPrint :: String -> [String] -> IO Bool
- data EventAttrs = EventAttrs {}
- emitPrintAttrs :: EventAttrs -> String -> [String] -> IO Bool
- sendModes :: [String] -> Int -> Char -> Char -> IO ()
- nickCmp :: String -> String -> IO Ordering
- strip :: Bool -> Bool -> String -> IO String
- getPrefs :: String -> (String -> IO a) -> (Int -> IO a) -> (Bool -> IO a) -> IO (Maybe a)
- getPrefString :: String -> IO (Maybe String)
- getPrefInt :: String -> IO (Maybe Int)
- getPrefBool :: String -> IO (Maybe Bool)
- data List
- listGet :: String -> IO (Maybe List)
- listFields :: String -> IO [String]
- listNext :: List -> IO Bool
- listStr :: List -> String -> IO String
- listInt :: List -> String -> IO Int
- listTime :: List -> String -> IO CTime
- pri_HIGHEST :: CInt
- pri_HIGH :: CInt
- pri_NORM :: CInt
- pri_LOW :: CInt
- pri_LOWEST :: CInt
- data Eat
- = EatNone
- | EatHexChat
- | EatPlugin
- | EatAll
- data Hook
- hookCommand :: String -> CInt -> String -> ([String] -> [String] -> IO Eat) -> IO Hook
- hookPrint :: String -> CInt -> ([String] -> IO Eat) -> IO Hook
- hookPrintAttrs :: String -> CInt -> ([String] -> EventAttrs -> IO Eat) -> IO Hook
- hookServer :: String -> CInt -> ([String] -> [String] -> IO Eat) -> IO Hook
- hookServerAttrs :: String -> CInt -> ([String] -> [String] -> EventAttrs -> IO Eat) -> IO Hook
- unhook :: Hook -> IO ()
- data Context
- findContext :: Maybe String -> Maybe String -> IO (Maybe Context)
- getContext :: IO Context
- setContext :: Context -> IO Bool
- withContext :: Context -> IO a -> IO a
Module Info
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 ~
and IO
()
, such as in the following:modDeinit
= id
info =modInfo
{modInit
= do x <- createXreturn
$ do destroyX x ,modDeinit
=id
}
Constructors
ModInfo | |
Fields
|
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 /
.
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 #
where sendModes
targets n sign modesign
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.
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.
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.
pri_HIGHEST :: CInt Source #
pri_LOWEST :: CInt 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. |
An opaque type referencing a particular hook. Can be passed to unhook
.
hookCommand :: String -> CInt -> String -> ([String] -> [String] -> IO Eat) -> IO Hook Source #
registers a command named hookCommand
cmd priority description fcmd
(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 #
hooks hookPrint
event priority ff
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 #
hooks hookPrintAttrs
event priority ff
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 #
hooks hookServer
word priority ff
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 #
hooks hookServer
word priority ff
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.
An opaque type referencing a context (tab or window).
findContext :: Maybe String -> Maybe String -> IO (Maybe Context) Source #
finds the context corresponding to the given tab name (or to the front tab if findContext
mserver mtabnameNothing
) in the given server (or in any of the servers if Nothing
).
getContext :: IO Context Source #
Obtains the current context.