emacs-module-0.1.1: Utilities to write Emacs dynamic modules

Copyright(c) Sergey Vinokurov 2018
LicenseBSD3-style (see LICENSE)
Maintainerserg.foo@gmail.com
Safe HaskellNone
LanguageHaskell2010

Emacs.Module.Monad.Class

Description

 
Synopsis

Documentation

type EmacsFunction req opt rest (s :: k) (m :: k -> Type -> Type) = (Throws EmacsThrow, Throws EmacsError, Throws EmacsInternalError, Throws UserError) => EmacsArgs req opt rest (EmacsRef m s) -> m s (EmacsReturn m s) Source #

Basic Haskell function that can be called by Emacs.

type EmacsFunctionExtra req opt rest extra (s :: k) (m :: k -> Type -> Type) = (Throws EmacsThrow, Throws EmacsError, Throws EmacsInternalError, Throws UserError) => EmacsArgs req opt rest (EmacsRef m s) -> Ptr extra -> m s (EmacsReturn m s) Source #

A Haskell functions that is callable by Emacs.

This type differs from EmacsFunction in that it has an extra parameter which will result in an additional pointer being passed to this function when it's called by Emacs. Contents of the pointer is specified when function is exported to Emacs.

class MonadEmacs (m :: k -> Type -> Type) where Source #

A mtl-style typeclass for interacting with Emacs. Typeclass functions are mostly direct translations of emacs interface provided by 'emacs-module.h'.

For more functions please refer to Emacs.Module.Functions module.

Associated Types

type EmacsRef m :: k -> Type Source #

Emacs value that is managed by the m monad. Will be cleaned up after m finishes its execution.

type EmacsReturn m :: k -> Type Source #

Type of values that Haskell functions may returns to Emacs.

Methods

produceRef :: EmacsRef m s -> m s (EmacsReturn m s) Source #

Return an EmacsRef back to Emacs.

nonLocalExitCheck :: WithCallStack => m s (FuncallExit ()) Source #

Check whether a non-local exit is pending.

nonLocalExitGet :: WithCallStack => m s (FuncallExit (EmacsRef m s, EmacsRef m s)) Source #

Check whether a non-local exit is pending and get detailed data in case it is.

nonLocalExitSignal Source #

Arguments

:: WithCallStack 
=> EmacsRef m s

Error symbol

-> [EmacsRef m s]

Error data, will be converted to a list as Emacs API expects.

-> m s () 

Equivalent to Emacs's signal function.

NB if a non-local exit is alredy pending, this function will not overwrite it. In order to do that, use nonLocalExitClear.

nonLocalExitThrow Source #

Arguments

:: WithCallStack 
=> EmacsRef m s

Tag

-> EmacsRef m s

Data

-> m s () 

Equivalent to Emacs's throw function.

NB if a non-local exit is alredy pending, this function will not overwrite it. In order to do that, use nonLocalExitClear.

nonLocalExitClear :: WithCallStack => m s () Source #

Clean any pending local exits.

freeValue :: WithCallStack => EmacsRef m s -> m s () Source #

Make value eligible for collection during next GC within Emacs.

makeFunctionExtra Source #

Arguments

:: (WithCallStack, EmacsInvocation req opt rest, GetArities req opt rest) 
=> (forall s'. EmacsFunctionExtra req opt rest extra s' m)

Haskell function to export

-> ByteString

Documentation

-> Ptr extra

Extra data to be passed to the Haskell function

-> m s (EmacsRef m s) 

Make Haskell function available as an anonymoucs Emacs function. In order to be able to use it later from Emacs it should be fed into bindFunction.

NB Each call to this function produces a small memory leak that will not be freed up. Hence, try not to create unbounded number of functions. This happens because GHC has to generate some wrapping code to convert between ccall and Haskell calling convention each time a function is exported. It is possible to free this code after function will not be used, but it's currently not supported.

funcall Source #

Arguments

:: WithCallStack 
=> SymbolName

Function name

-> [EmacsRef m s]

Arguments

-> m s (EmacsRef m s) 

Invoke an Emacs function that may call back into Haskell.

funcallPrimitive Source #

Arguments

:: WithCallStack 
=> SymbolName

Function name

-> [EmacsRef m s]

Arguments

-> m s (EmacsRef m s) 

Invoke an Emacs function. The function should be simple and must not call back into Haskell.

funcallPrimitive_ Source #

Arguments

:: WithCallStack 
=> SymbolName

Function name

-> [EmacsRef m s]

Arguments

-> m s () 

Invoke an Emacs function and ignore its result. The function should be simple and must not call back into Haskell.

intern :: WithCallStack => SymbolName -> m s (EmacsRef m s) Source #

Convert a string to an Emacs symbol.

typeOf :: WithCallStack => EmacsRef m s -> m s (EmacsRef m s) Source #

Get type of an Emacs value as an Emacs symbol.

isNotNil :: WithCallStack => EmacsRef m s -> m s Bool Source #

Check whether Emacs value is not nil.

eq :: WithCallStack => EmacsRef m s -> EmacsRef m s -> m s Bool Source #

Primitive equality. Tests whether two symbols, integers or characters are the equal, but not much more. For more complete equality comparison do

funcallPrimitive [esym|equal|] [x, y]

extractWideInteger :: WithCallStack => EmacsRef m s -> m s Int64 Source #

Try to unpack a wide integer from a value.

makeWideInteger :: WithCallStack => Int64 -> m s (EmacsRef m s) Source #

Pack a wide integer for Emacs.

extractDouble :: WithCallStack => EmacsRef m s -> m s Double Source #

Try to unpack a floating-point number from a value.

makeDouble :: WithCallStack => Double -> m s (EmacsRef m s) Source #

Convert a floating-point number into Emacs value.

extractString :: WithCallStack => EmacsRef m s -> m s ByteString Source #

Extract string contents from an Emacs value.

makeString :: WithCallStack => ByteString -> m s (EmacsRef m s) Source #

Convert a utf8-encoded ByteString into an Emacs value.

extractUserPtr :: WithCallStack => EmacsRef m s -> m s (Ptr a) Source #

Extract a user pointer from an Emacs value.

makeUserPtr Source #

Arguments

:: WithCallStack 
=> UserPtrFinaliser a

Finalisation action that will be executed when user pointer gets garbage-collected by Emacs.

-> Ptr a 
-> m s (EmacsRef m s) 

Pack a user pointer into an Emacs value.

assignUserPtr :: WithCallStack => EmacsRef m s -> Ptr a -> m s () Source #

Set user pointer to a new value

extractUserPtrFinaliser :: WithCallStack => EmacsRef m s -> m s (UserPtrFinaliser a) Source #

Extract a finaliser from an user_ptr.

assignUserPtrFinaliser :: WithCallStack => EmacsRef m s -> UserPtrFinaliser a -> m s () Source #

Assign new finaliser into an user_ptr.

vecGet :: WithCallStack => EmacsRef m s -> Int -> m s (EmacsRef m s) Source #

Extract an element from an Emacs vector.

vecSet Source #

Arguments

:: WithCallStack 
=> EmacsRef m s

Vector

-> Int

Index

-> EmacsRef m s

New value

-> m s () 

Assign an element into an Emacs vector.

vecSize :: WithCallStack => EmacsRef m s -> m s Int Source #

Get size of an Emacs vector.

Instances
(Throws EmacsThrow, Throws EmacsError, Throws EmacsInternalError) => MonadEmacs EmacsM Source # 
Instance details

Defined in Emacs.Module.Monad

Associated Types

type EmacsRef EmacsM :: k -> Type Source #

type EmacsReturn EmacsM :: k -> Type Source #

Methods

produceRef :: EmacsRef EmacsM s -> EmacsM s (EmacsReturn EmacsM s) Source #

nonLocalExitCheck :: WithCallStack => EmacsM s (FuncallExit ()) Source #

nonLocalExitGet :: WithCallStack => EmacsM s (FuncallExit (EmacsRef EmacsM s, EmacsRef EmacsM s)) Source #

nonLocalExitSignal :: WithCallStack => EmacsRef EmacsM s -> [EmacsRef EmacsM s] -> EmacsM s () Source #

nonLocalExitThrow :: WithCallStack => EmacsRef EmacsM s -> EmacsRef EmacsM s -> EmacsM s () Source #

nonLocalExitClear :: WithCallStack => EmacsM s () Source #

freeValue :: WithCallStack => EmacsRef EmacsM s -> EmacsM s () Source #

makeFunctionExtra :: (WithCallStack, EmacsInvocation req opt rest, GetArities req opt rest) => (forall (s' :: k). (Throws EmacsThrow, Throws EmacsError, Throws EmacsInternalError, Throws UserError) => EmacsArgs req opt rest (EmacsRef EmacsM s') -> Ptr extra -> EmacsM s' (EmacsReturn EmacsM s')) -> ByteString -> Ptr extra -> EmacsM s (EmacsRef EmacsM s) Source #

funcall :: WithCallStack => SymbolName -> [EmacsRef EmacsM s] -> EmacsM s (EmacsRef EmacsM s) Source #

funcallPrimitive :: WithCallStack => SymbolName -> [EmacsRef EmacsM s] -> EmacsM s (EmacsRef EmacsM s) Source #

funcallPrimitive_ :: WithCallStack => SymbolName -> [EmacsRef EmacsM s] -> EmacsM s () Source #

intern :: WithCallStack => SymbolName -> EmacsM s (EmacsRef EmacsM s) Source #

typeOf :: WithCallStack => EmacsRef EmacsM s -> EmacsM s (EmacsRef EmacsM s) Source #

isNotNil :: WithCallStack => EmacsRef EmacsM s -> EmacsM s Bool Source #

eq :: WithCallStack => EmacsRef EmacsM s -> EmacsRef EmacsM s -> EmacsM s Bool Source #

extractWideInteger :: WithCallStack => EmacsRef EmacsM s -> EmacsM s Int64 Source #

makeWideInteger :: WithCallStack => Int64 -> EmacsM s (EmacsRef EmacsM s) Source #

extractDouble :: WithCallStack => EmacsRef EmacsM s -> EmacsM s Double Source #

makeDouble :: WithCallStack => Double -> EmacsM s (EmacsRef EmacsM s) Source #

extractString :: WithCallStack => EmacsRef EmacsM s -> EmacsM s ByteString Source #

makeString :: WithCallStack => ByteString -> EmacsM s (EmacsRef EmacsM s) Source #

extractUserPtr :: WithCallStack => EmacsRef EmacsM s -> EmacsM s (Ptr a) Source #

makeUserPtr :: WithCallStack => UserPtrFinaliser a -> Ptr a -> EmacsM s (EmacsRef EmacsM s) Source #

assignUserPtr :: WithCallStack => EmacsRef EmacsM s -> Ptr a -> EmacsM s () Source #

extractUserPtrFinaliser :: WithCallStack => EmacsRef EmacsM s -> EmacsM s (UserPtrFinaliser a) Source #

assignUserPtrFinaliser :: WithCallStack => EmacsRef EmacsM s -> UserPtrFinaliser a -> EmacsM s () Source #

vecGet :: WithCallStack => EmacsRef EmacsM s -> Int -> EmacsM s (EmacsRef EmacsM s) Source #

vecSet :: WithCallStack => EmacsRef EmacsM s -> Int -> EmacsRef EmacsM s -> EmacsM s () Source #

vecSize :: WithCallStack => EmacsRef EmacsM s -> EmacsM s Int Source #