Copyright | (c) Sergey Vinokurov 2018 |
---|---|
License | Apache-2.0 (see LICENSE) |
Maintainer | serg.foo@gmail.com |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
Synopsis
- type EmacsFunction req opt rest (m :: k -> Type -> Type) (v :: k -> Type) (s :: k) = EmacsArgs req opt rest (v s) -> m s (v s)
- 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
- makeGlobalRef :: WithCallStack => v s -> m s (RawValue 'Pinned)
- freeGlobalRef :: WithCallStack => RawValue 'Pinned -> m s ()
- nonLocalExitCheck :: WithCallStack => m s (FuncallExit ())
- nonLocalExitGet :: WithCallStack => m s (FuncallExit (v s, v s))
- nonLocalExitSignal :: (WithCallStack, Foldable f) => v s -> f (v s) -> m s ()
- nonLocalExitThrow :: WithCallStack => v s -> v s -> m s ()
- nonLocalExitClear :: WithCallStack => m s ()
- makeFunction :: (WithCallStack, EmacsInvocation req opt rest, GetArities req opt rest) => (forall s'. EmacsFunction req opt rest m v s') -> Doc -> m s (v s)
- funcall :: (WithCallStack, Foldable f) => v s -> f (v s) -> m s (v s)
- funcallPrimitive :: (WithCallStack, Foldable f) => v s -> f (v s) -> m s (v s)
- funcallPrimitiveUnchecked :: (WithCallStack, Foldable f) => v s -> f (v s) -> m s (v s)
- intern :: WithCallStack => SymbolName -> m s (v s)
- typeOf :: WithCallStack => v s -> m s (v s)
- isNotNil :: WithCallStack => v s -> m s Bool
- eq :: WithCallStack => v s -> v s -> m s Bool
- extractWideInteger :: WithCallStack => v s -> m s Int64
- makeWideInteger :: WithCallStack => Int64 -> m s (v s)
- extractDouble :: WithCallStack => v s -> m s Double
- makeDouble :: WithCallStack => Double -> m s (v s)
- extractText :: WithCallStack => v s -> m s Text
- extractShortByteString :: WithCallStack => v s -> m s ShortByteString
- makeString :: WithCallStack => ByteString -> m s (v s)
- makeBinaryString :: WithCallStack => ByteString -> m s (v s)
- extractUserPtr :: WithCallStack => v s -> m s (Ptr a)
- makeUserPtr :: WithCallStack => FinalizerPtr a -> Ptr a -> m s (v s)
- assignUserPtr :: WithCallStack => v s -> Ptr a -> m s ()
- extractUserPtrFinaliser :: WithCallStack => v s -> m s (FinalizerPtr a)
- assignUserPtrFinaliser :: WithCallStack => v s -> FinalizerPtr a -> m s ()
- vecGet :: WithCallStack => v s -> Int -> m s (v s)
- unsafeVecGet :: WithCallStack => v s -> Int -> m s (v s)
- vecSet :: WithCallStack => v s -> Int -> v s -> m s ()
- vecSize :: WithCallStack => v s -> m s Int
- processInput :: WithCallStack => m s Result
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.
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.
:: (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
.
:: 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.
:: (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
.
:: (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.
:: (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 #
:: (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.
makeBinaryString :: WithCallStack => ByteString -> m s (v s) Source #
Convert any ByteString into an Emacs unibyte string.
extractUserPtr :: WithCallStack => v s -> m s (Ptr a) Source #
Extract a user pointer from an Emacs value.
:: 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.
:: 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.