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

Description

This module is the entry point for writing Emacs extensions in Haskell.

This package, though provides a lot of wrapping around Emacs's bare C interface, still presumes some familiarity with said interface. Thus, when developnig Emacs modules it's recommended to keep a reference of the C interface around. One such reference is https://phst.github.io/emacs-modules.html.

Minimalistic example

Consider Emacs function

(defun foo (f x y z &optional w t &rest quux)
  (+ (funcall f (* x y z)) (* (or w 1) (or t 2)) (length quux)))

With help of this package, it may be defined as

{-# LANGUAGE DataKinds   #-}
{-# LANGUAGE QuasiQuotes #-}

import Data.Maybe
import Data.Emacs.Module.SymbolName.TH
import Emacs.Module
foo
  :: MonadEmacs m v
  => EmacsFunction ('S ('S ('S ('S 'Z)))) ('S ('S 'Z)) 'True m v s
foo (R f (R x (R y (R z (O w (O t (Rest quux))))))) = do
  x'    <- extractInt x
  y'    <- extractInt y
  z'    <- extractInt z
  w'    <- traverse extractInt w
  t'    <- traverse extractInt t

  tmp   <- makeInt (x' * y' * z')
  tmp'  <- extractInt =<< funcallSym "funcall" [f, tmp]

  produceRef =<< makeInt (tmp' + fromMaybe 1 w' * fromMaybe 2 t' + length quux)

Creating Emacs dynamic module

In order to make shared object or dll callable from Emacs, a cabal project with foreign-library section has to be created. Please refer to https://github.com/sergv/emacs-module/tree/master/test for such a project.

Please note that this project will need a small C file for initialising Haskell runtime. In the project mentioned before it's present as https://github.com/sergv/emacs-module/blob/master/test/cbits/emacs_wrapper.c

Synopsis

Basic bindings

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 #

Define functions callable by Emacs

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.

data Nat Source #

Type-level Peano numbers.

Indented to be used with DataKinds extension enabled.

Constructors

Z 
S Nat 

data R a b Source #

Required argument of an exported function.

Constructors

R !a !b 

data O a b Source #

Optional argument of an exported function.

Constructors

O !(Maybe a) !b 

newtype Rest a Source #

All other arguments of an exported function as a list.

Constructors

Rest [a] 

data Stop a Source #

End of argument list of an exported funciton.

Constructors

Stop 

Error types

data EmacsError Source #

A high-level error thrown when an Emacs function fails.

Instances

Instances details
Exception EmacsError Source # 
Instance details

Defined in Emacs.Module.Errors

Show EmacsError Source # 
Instance details

Defined in Emacs.Module.Errors

Pretty EmacsError Source # 
Instance details

Defined in Emacs.Module.Errors

Methods

pretty :: EmacsError -> Doc ann #

prettyList :: [EmacsError] -> Doc ann #

data EmacsInternalError Source #

A low-level error thrown when assumptions of this package are violated and it's not safe to proceed further.

E.g. Emacs returned value not specified in a C enum - cannot really process it in a meaningful way.

reportAllErrorsToEmacs Source #

Arguments

:: Env 
-> IO a

Result to return on error.

-> IO a 
-> IO a 

Catch all errors this package might throw in an IO action and make Emacs aware of them.

This is a convenience function intended to be used around exported initialise entry point into an Emacs module.

Reexports

data Env Source #

Emacs environment, right from the 'emacs-module.h'.

Third-party reexports

class Monad m => MonadThrow (m :: Type -> Type) where #

A class for monads in which exceptions may be thrown.

Instances should obey the following law:

throwM e >> x = throwM e

In other words, throwing an exception short-circuits the rest of the monadic computation.

Methods

throwM :: (HasCallStack, Exception e) => e -> m a #

Throw an exception. Note that this throws when this action is run in the monad m, not when it is applied. It is a generalization of Control.Exception's throwIO.

Should satisfy the law:

throwM e >> f = throwM e

Instances

Instances details
MonadThrow STM 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> STM a #

MonadThrow IO 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> IO a #

MonadThrow Q 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> Q a #

MonadThrow Maybe 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> Maybe a #

MonadThrow [] 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> [a] #

e ~ SomeException => MonadThrow (Either e) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e0) => e0 -> Either e a #

MonadThrow (ST s) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> ST s a #

MonadThrow m => MonadThrow (ListT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> ListT m a #

MonadThrow m => MonadThrow (MaybeT m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> MaybeT m a #

MonadThrow (EmacsM s) Source # 
Instance details

Defined in Emacs.Module.Monad

Methods

throwM :: (HasCallStack, Exception e) => e -> EmacsM s a #

(Error e, MonadThrow m) => MonadThrow (ErrorT e m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e0) => e0 -> ErrorT e m a #

MonadThrow m => MonadThrow (ExceptT e m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e0) => e0 -> ExceptT e m a #

MonadThrow m => MonadThrow (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> IdentityT m a #

MonadThrow m => MonadThrow (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> ReaderT r m a #

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> StateT s m a #

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> StateT s m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> WriterT w m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> WriterT w m a #

MonadThrow m => MonadThrow (ContT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> ContT r m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> RWST r w s m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e) => e -> RWST r w s m a #