emacs-module-0.2: Utilities to write Emacs dynamic modules
Copyright(c) Sergey Vinokurov 2018
LicenseApache-2.0 (see LICENSE)
Maintainerserg.foo@gmail.com
Safe HaskellSafe-Inferred
LanguageGHC2021

Emacs.Module.Monad.Class

Description

 
Synopsis

Documentation

type EmacsFunction req opt rest (m :: k -> Type -> Type) (v :: k -> Type) (s :: k) = EmacsArgs req opt rest (v s) -> m s (v s) Source #

Basic Haskell function that can be called by Emacs.

class (forall s. Monad (m s), forall s. MonadInterleave (m s), forall s. Unbox (v s), forall s. PrimMonad (m s)) => MonadEmacs (m :: k -> Type -> Type) (v :: k -> Type) | m -> v 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.

Methods

makeGlobalRef :: WithCallStack => v s -> m s (RawValue 'Pinned) Source #

Make a global reference to a value so that it will persist across different calls from Emacs into exposed functions.

freeGlobalRef :: WithCallStack => RawValue 'Pinned -> m s () Source #

Free a global reference.

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

Check whether a non-local exit is pending.

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

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

nonLocalExitSignal Source #

Arguments

:: (WithCallStack, Foldable f) 
=> v s

Error symbol

-> f (v s)

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

-> m s () 

Equivalent to Emacs's signal function. Terminates current computation.

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

nonLocalExitThrow Source #

Arguments

:: WithCallStack 
=> v s

Tag

-> v s

Data

-> m s () 

Equivalent to Emacs's throw function. Terminates current computation.

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.

makeFunction Source #

Arguments

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

Haskell function to export

-> Doc

Documentation

-> m s (v s) 

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

funcall Source #

Arguments

:: (WithCallStack, Foldable f) 
=> v s

Function name

-> f (v s)

Arguments

-> m s (v s) 

Invoke an Emacs function that may call back into Haskell.

funcallPrimitive Source #

Arguments

:: (WithCallStack, Foldable f) 
=> v s

Function name

-> f (v s)

Arguments

-> m s (v s) 

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

funcallPrimitiveUnchecked Source #

Arguments

:: (WithCallStack, Foldable f) 
=> v s

Function name

-> f (v s)

Arguments

-> m s (v s) 

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

Exit status is not checked - function is expected to always succeed. Consult Emacs side to make sure that's the case. Examples of safe functions: cons, list, vector, etc.

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

Convert a string to an Emacs symbol.

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

Get type of an Emacs value as an Emacs symbol.

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

Check whether Emacs value is not nil.

eq :: WithCallStack => v s -> v 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

intern "equal" >>= \equal -> funcallPrimitiveUnchecked equal [x, y]

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

Try to unpack a wide integer from a value.

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

Pack a wide integer for Emacs.

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

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

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

Convert a floating-point number into Emacs value.

extractText :: WithCallStack => v s -> m s Text Source #

Extract string contents from an Emacs value.

extractShortByteString :: WithCallStack => v s -> m s ShortByteString Source #

Extract string contents from an Emacs value as utf8-encoded short bytestring.

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

Convert a utf8-encoded ByteString into an Emacs value.

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

Extract a user pointer from an Emacs value.

makeUserPtr Source #

Arguments

:: WithCallStack 
=> FinalizerPtr a

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

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

Pack a user pointer into an Emacs value.

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

Set user pointer to a new value

extractUserPtrFinaliser :: WithCallStack => v s -> m s (FinalizerPtr a) Source #

Extract a finaliser from an user_ptr.

assignUserPtrFinaliser :: WithCallStack => v s -> FinalizerPtr a -> m s () Source #

Assign new finaliser into an user_ptr.

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

Extract an element from an Emacs vector.

unsafeVecGet :: WithCallStack => v s -> Int -> m s (v s) Source #

Extract an element from an Emacs vector without checking for errors.

vecSet Source #

Arguments

:: WithCallStack 
=> v s

Vector

-> Int

Index

-> v s

New value

-> m s () 

Assign an element into an Emacs vector.

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

Get size of an Emacs vector.

processInput :: WithCallStack => m s Result Source #

Check whether user pressed 'C-g' and we should abort our operation.

Instances

Instances details
MonadEmacs (EmacsM :: k -> Type -> TYPE LiftedRep) (Value :: k -> TYPE LiftedRep) Source # 
Instance details

Defined in Emacs.Module.Monad

Methods

makeGlobalRef :: forall (s :: k0). WithCallStack => Value s -> EmacsM s (RawValue 'Pinned) Source #

freeGlobalRef :: forall (s :: k0). WithCallStack => RawValue 'Pinned -> EmacsM s () Source #

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

nonLocalExitGet :: forall (s :: k0). WithCallStack => EmacsM s (FuncallExit (Value s, Value s)) Source #

nonLocalExitSignal :: forall f (s :: k0). (WithCallStack, Foldable f) => Value s -> f (Value s) -> EmacsM s () Source #

nonLocalExitThrow :: forall (s :: k0). WithCallStack => Value s -> Value s -> EmacsM s () Source #

nonLocalExitClear :: forall (s :: k0). WithCallStack => EmacsM s () Source #

makeFunction :: forall (req :: Nat) (opt :: Nat) (rest :: Bool) (s :: k0). (WithCallStack, EmacsInvocation req opt rest, GetArities req opt rest) => (forall (s' :: k0). EmacsFunction req opt rest EmacsM Value s') -> Doc -> EmacsM s (Value s) Source #

funcall :: forall f (s :: k0). (WithCallStack, Foldable f) => Value s -> f (Value s) -> EmacsM s (Value s) Source #

funcallPrimitive :: forall f (s :: k0). (WithCallStack, Foldable f) => Value s -> f (Value s) -> EmacsM s (Value s) Source #

funcallPrimitiveUnchecked :: forall f (s :: k0). (WithCallStack, Foldable f) => Value s -> f (Value s) -> EmacsM s (Value s) Source #

intern :: forall (s :: k0). WithCallStack => SymbolName -> EmacsM s (Value s) Source #

typeOf :: forall (s :: k0). WithCallStack => Value s -> EmacsM s (Value s) Source #

isNotNil :: forall (s :: k0). WithCallStack => Value s -> EmacsM s Bool Source #

eq :: forall (s :: k0). WithCallStack => Value s -> Value s -> EmacsM s Bool Source #

extractWideInteger :: forall (s :: k0). WithCallStack => Value s -> EmacsM s Int64 Source #

makeWideInteger :: forall (s :: k0). WithCallStack => Int64 -> EmacsM s (Value s) Source #

extractDouble :: forall (s :: k0). WithCallStack => Value s -> EmacsM s Double Source #

makeDouble :: forall (s :: k0). WithCallStack => Double -> EmacsM s (Value s) Source #

extractText :: forall (s :: k0). WithCallStack => Value s -> EmacsM s Text Source #

extractShortByteString :: forall (s :: k0). WithCallStack => Value s -> EmacsM s ShortByteString Source #

makeString :: forall (s :: k0). WithCallStack => ByteString -> EmacsM s (Value s) Source #

extractUserPtr :: forall (s :: k0) a. WithCallStack => Value s -> EmacsM s (Ptr a) Source #

makeUserPtr :: forall a (s :: k0). WithCallStack => FinalizerPtr a -> Ptr a -> EmacsM s (Value s) Source #

assignUserPtr :: forall (s :: k0) a. WithCallStack => Value s -> Ptr a -> EmacsM s () Source #

extractUserPtrFinaliser :: forall (s :: k0) a. WithCallStack => Value s -> EmacsM s (FinalizerPtr a) Source #

assignUserPtrFinaliser :: forall (s :: k0) a. WithCallStack => Value s -> FinalizerPtr a -> EmacsM s () Source #

vecGet :: forall (s :: k0). WithCallStack => Value s -> Int -> EmacsM s (Value s) Source #

unsafeVecGet :: forall (s :: k0). WithCallStack => Value s -> Int -> EmacsM s (Value s) Source #

vecSet :: forall (s :: k0). WithCallStack => Value s -> Int -> Value s -> EmacsM s () Source #

vecSize :: forall (s :: k0). WithCallStack => Value s -> EmacsM s Int Source #

processInput :: forall (s :: k0). WithCallStack => EmacsM s Result Source #