Copyright | (c) Sergey Vinokurov 2018 |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | serg.foo@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Env
- data FuncallExit a
- funcallExitToNum :: Num a => FuncallExit b -> a
- funcallExitFromNum :: (Eq a, Num a) => a -> Maybe (FuncallExit ())
- newtype EnumFuncallExit = EnumFuncallExit {}
- type UserPtrFinaliserType a = Ptr a -> IO ()
- type UserPtrFinaliser a = FunPtr (UserPtrFinaliserType a)
- isValidEnv :: MonadIO m => Env -> m Bool
- makeGlobalRef :: forall m. MonadIO m => Env -> RawValue -> m GlobalRef
- freeGlobalRef :: forall m. MonadIO m => Env -> GlobalRef -> m ()
- nonLocalExitCheck :: MonadIO m => Env -> m EnumFuncallExit
- nonLocalExitGet :: MonadIO m => Env -> NonNullPtr RawValue -> NonNullPtr RawValue -> m EnumFuncallExit
- nonLocalExitSignal :: MonadIO m => Env -> RawValue -> RawValue -> m ()
- nonLocalExitThrow :: MonadIO m => Env -> RawValue -> RawValue -> m ()
- nonLocalExitClear :: MonadIO m => Env -> m ()
- variadicFunctionArgs :: CPtrdiff
- makeFunction :: forall m a. MonadIO m => Env -> CPtrdiff -> CPtrdiff -> RawFunction a -> CString -> Ptr a -> m RawValue
- funcall :: MonadIO m => Env -> RawValue -> CPtrdiff -> NonNullPtr RawValue -> m RawValue
- funcallPrimitive :: MonadIO m => Env -> RawValue -> CPtrdiff -> NonNullPtr RawValue -> m RawValue
- intern :: MonadIO m => Env -> CString -> m RawValue
- typeOf :: MonadIO m => Env -> RawValue -> m RawValue
- isNotNil :: MonadIO m => Env -> RawValue -> m CBoolean
- eq :: MonadIO m => Env -> RawValue -> RawValue -> m CBoolean
- extractInteger :: MonadIO m => Env -> RawValue -> m CIntMax
- makeInteger :: MonadIO m => Env -> CIntMax -> m RawValue
- extractFloat :: MonadIO m => Env -> RawValue -> m CDouble
- makeFloat :: MonadIO m => Env -> CDouble -> m RawValue
- copyStringContents :: MonadIO m => Env -> RawValue -> CString -> NonNullPtr CPtrdiff -> m CBoolean
- makeString :: MonadIO m => Env -> CString -> CPtrdiff -> m RawValue
- makeUserPtr :: forall m a. MonadIO m => Env -> UserPtrFinaliser a -> Ptr a -> m RawValue
- getUserPtr :: MonadIO m => Env -> RawValue -> m (Ptr a)
- setUserPtr :: MonadIO m => Env -> RawValue -> Ptr a -> m ()
- getUserFinaliser :: MonadIO m => Env -> RawValue -> m (UserPtrFinaliser a)
- setUserFinaliser :: MonadIO m => Env -> RawValue -> UserPtrFinaliser a -> m ()
- vecGet :: MonadIO m => Env -> RawValue -> CPtrdiff -> m RawValue
- vecSet :: MonadIO m => Env -> RawValue -> CPtrdiff -> RawValue -> m ()
- vecSize :: MonadIO m => Env -> RawValue -> m CPtrdiff
- exportToEmacs :: RawFunctionType a -> IO (RawFunction a)
- type RawFunctionType a = Env -> CPtrdiff -> Ptr RawValue -> Ptr a -> IO RawValue
- data RawFunction a
- freeStablePtrFinaliser :: UserPtrFinaliser a
Documentation
enum emacs_funcall_exit
data FuncallExit a Source #
Possible Emacs function call outcomes. This is Haskell's version of
FuncallExitReturn | Function has returned normally. |
FuncallExitSignal a | Function has signaled an error using |
FuncallExitThrow a | Function has exit using |
Instances
funcallExitToNum :: Num a => FuncallExit b -> a Source #
funcallExitFromNum :: (Eq a, Num a) => a -> Maybe (FuncallExit ()) Source #
Wrappers around struct emacs_env fields
newtype EnumFuncallExit Source #
type UserPtrFinaliserType a = Ptr a -> IO () Source #
type UserPtrFinaliser a = FunPtr (UserPtrFinaliserType a) Source #
isValidEnv :: MonadIO m => Env -> m Bool Source #
Check wheter passed emacs_env
structure has expected size so that
we will be able to access all of its fields.
freeGlobalRef :: forall m. MonadIO m => Env -> GlobalRef -> m () Source #
nonLocalExitCheck :: MonadIO m => Env -> m EnumFuncallExit Source #
:: MonadIO m | |
=> Env | |
-> NonNullPtr RawValue | Symbol output |
-> NonNullPtr RawValue | Data output |
-> m EnumFuncallExit |
nonLocalExitClear :: MonadIO m => Env -> m () Source #
:: MonadIO m | |
=> Env | |
-> RawValue | Emacs value that holds a string |
-> CString | Destination, may be NULL |
-> NonNullPtr CPtrdiff | SIZE pointer |
-> m CBoolean |
Copy the content of the Lisp string VALUE to BUFFER as an utf8 null-terminated string.
SIZE must point to the total size of the buffer. If BUFFER is NULL or if SIZE is not big enough, write the required buffer size to SIZE and return true.
Note that SIZE must include the last null byte (e.g. "abc" needs a buffer of size 4).
Return true if the string was successfully copied.
makeUserPtr :: forall m a. MonadIO m => Env -> UserPtrFinaliser a -> Ptr a -> m RawValue Source #
getUserFinaliser :: MonadIO m => Env -> RawValue -> m (UserPtrFinaliser a) Source #
setUserFinaliser :: MonadIO m => Env -> RawValue -> UserPtrFinaliser a -> m () Source #
Expose functions to Emacs
exportToEmacs :: RawFunctionType a -> IO (RawFunction a) Source #
data RawFunction a Source #
Expose Haskell data to Emacs
freeStablePtrFinaliser :: UserPtrFinaliser a Source #
Pass to makeUserPtr
so that Emacs will free the Haskell's stable
pointer when the corresponding elisp value goes out of scope.