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

Data.Emacs.Module.Env

Description

 
Synopsis

Documentation

data Env Source #

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

enum emacs_funcall_exit

data FuncallExit a Source #

Possible Emacs function call outcomes. This is Haskell's version of

Constructors

FuncallExitReturn

Function has returned normally.

FuncallExitSignal a

Function has signaled an error using signal.

FuncallExitThrow a

Function has exit using throw.

Instances

Instances details
Foldable FuncallExit Source # 
Instance details

Defined in Data.Emacs.Module.Env.Functions

Methods

fold :: Monoid m => FuncallExit m -> m #

foldMap :: Monoid m => (a -> m) -> FuncallExit a -> m #

foldMap' :: Monoid m => (a -> m) -> FuncallExit a -> m #

foldr :: (a -> b -> b) -> b -> FuncallExit a -> b #

foldr' :: (a -> b -> b) -> b -> FuncallExit a -> b #

foldl :: (b -> a -> b) -> b -> FuncallExit a -> b #

foldl' :: (b -> a -> b) -> b -> FuncallExit a -> b #

foldr1 :: (a -> a -> a) -> FuncallExit a -> a #

foldl1 :: (a -> a -> a) -> FuncallExit a -> a #

toList :: FuncallExit a -> [a] #

null :: FuncallExit a -> Bool #

length :: FuncallExit a -> Int #

elem :: Eq a => a -> FuncallExit a -> Bool #

maximum :: Ord a => FuncallExit a -> a #

minimum :: Ord a => FuncallExit a -> a #

sum :: Num a => FuncallExit a -> a #

product :: Num a => FuncallExit a -> a #

Traversable FuncallExit Source # 
Instance details

Defined in Data.Emacs.Module.Env.Functions

Methods

traverse :: Applicative f => (a -> f b) -> FuncallExit a -> f (FuncallExit b) #

sequenceA :: Applicative f => FuncallExit (f a) -> f (FuncallExit a) #

mapM :: Monad m => (a -> m b) -> FuncallExit a -> m (FuncallExit b) #

sequence :: Monad m => FuncallExit (m a) -> m (FuncallExit a) #

Functor FuncallExit Source # 
Instance details

Defined in Data.Emacs.Module.Env.Functions

Methods

fmap :: (a -> b) -> FuncallExit a -> FuncallExit b #

(<$) :: a -> FuncallExit b -> FuncallExit a #

Data a => Data (FuncallExit a) Source # 
Instance details

Defined in Data.Emacs.Module.Env.Functions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FuncallExit a -> c (FuncallExit a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FuncallExit a) #

toConstr :: FuncallExit a -> Constr #

dataTypeOf :: FuncallExit a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FuncallExit a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FuncallExit a)) #

gmapT :: (forall b. Data b => b -> b) -> FuncallExit a -> FuncallExit a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FuncallExit a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FuncallExit a -> r #

gmapQ :: (forall d. Data d => d -> u) -> FuncallExit a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FuncallExit a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FuncallExit a -> m (FuncallExit a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FuncallExit a -> m (FuncallExit a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FuncallExit a -> m (FuncallExit a) #

Generic (FuncallExit a) Source # 
Instance details

Defined in Data.Emacs.Module.Env.Functions

Associated Types

type Rep (FuncallExit a) :: Type -> Type #

Methods

from :: FuncallExit a -> Rep (FuncallExit a) x #

to :: Rep (FuncallExit a) x -> FuncallExit a #

Show a => Show (FuncallExit a) Source # 
Instance details

Defined in Data.Emacs.Module.Env.Functions

Eq a => Eq (FuncallExit a) Source # 
Instance details

Defined in Data.Emacs.Module.Env.Functions

Ord a => Ord (FuncallExit a) Source # 
Instance details

Defined in Data.Emacs.Module.Env.Functions

Pretty a => Pretty (FuncallExit a) Source # 
Instance details

Defined in Data.Emacs.Module.Env.Functions

Methods

pretty :: FuncallExit a -> Doc ann #

prettyList :: [FuncallExit a] -> Doc ann #

Lift a => Lift (FuncallExit a :: Type) Source # 
Instance details

Defined in Data.Emacs.Module.Env.Functions

Methods

lift :: Quote m => FuncallExit a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FuncallExit a -> Code m (FuncallExit a) #

type Rep (FuncallExit a) Source # 
Instance details

Defined in Data.Emacs.Module.Env.Functions

type Rep (FuncallExit a) = D1 ('MetaData "FuncallExit" "Data.Emacs.Module.Env.Functions" "emacs-module-0.2.1-LqesOn6xic3Iyo1jMFpGm8" 'False) (C1 ('MetaCons "FuncallExitReturn" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FuncallExitSignal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "FuncallExitThrow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))))

Wrappers around struct emacs_env fields

newtype EnumFuncallExit Source #

Constructors

EnumFuncallExit 

Instances

Instances details
Pretty EnumFuncallExit Source # 
Instance details

Defined in Data.Emacs.Module.Raw.Env

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.

makeGlobalRef :: forall m p. MonadIO m => Env -> RawValue p -> m (RawValue 'Pinned) Source #

freeGlobalRef :: forall m. MonadIO m => Env -> RawValue 'Pinned -> m () Source #

nonLocalExitGet Source #

Arguments

:: MonadIO m 
=> Env 
-> NonNullPtr (RawValue 'Regular)

Symbol output

-> NonNullPtr (RawValue 'Regular)

Data output

-> m EnumFuncallExit 

nonLocalExitSignal Source #

Arguments

:: MonadIO m 
=> Env 
-> RawValue p1

Error symbol

-> RawValue p2

Error data

-> m () 

nonLocalExitThrow Source #

Arguments

:: MonadIO m 
=> Env 
-> RawValue p1

Tag, a symbol

-> RawValue p2

Value

-> m () 

makeFunction Source #

Arguments

:: forall m o a. MonadIO m 
=> Env 
-> CPtrdiff

Minimum arity

-> CPtrdiff

Maximum arity

-> RawFunction o a

Implementation

-> CString

Documentation

-> Ptr a

Extra data

-> m (RawValue 'Regular) 

funcall Source #

Arguments

:: MonadIO m 
=> Env 
-> RawValue p1

Function

-> CPtrdiff

Number of arguments

-> NonNullPtr (RawValue p2)

Actual arguments

-> m (RawValue 'Regular) 

funcallPrimitive Source #

Arguments

:: MonadIO m 
=> Env 
-> RawValue p1

Function

-> CPtrdiff

Number of arguments

-> NonNullPtr (RawValue p2)

Actual arguments

-> m (RawValue 'Regular) 

intern :: MonadIO m => Env -> CString -> m (RawValue 'Regular) Source #

typeOf :: MonadIO m => Env -> RawValue p -> m (RawValue 'Regular) Source #

isNotNil :: MonadIO m => Env -> RawValue p -> m CBoolean Source #

eq :: MonadIO m => Env -> RawValue p1 -> RawValue p2 -> m CBoolean Source #

extractInteger :: MonadIO m => Env -> RawValue p -> m CIntMax Source #

makeInteger :: MonadIO m => Env -> CIntMax -> m (RawValue 'Regular) Source #

extractFloat :: MonadIO m => Env -> RawValue p -> m CDouble Source #

makeFloat :: MonadIO m => Env -> CDouble -> m (RawValue 'Regular) Source #

copyStringContents Source #

Arguments

:: MonadIO m 
=> Env 
-> RawValue p

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.

makeString Source #

Arguments

:: MonadIO m 
=> Env 
-> CString

Utf8-encoded string, may contain null bytes and is not required to be terminated with one.

-> CPtrdiff

Length.

-> m (RawValue 'Regular) 

makeUserPtr :: forall m a. MonadIO m => Env -> FinalizerPtr a -> Ptr a -> m (RawValue 'Regular) Source #

getUserPtr :: MonadIO m => Env -> RawValue p -> m (Ptr a) Source #

setUserPtr :: MonadIO m => Env -> RawValue p -> Ptr a -> m () Source #

getUserFinaliser :: MonadIO m => Env -> RawValue p -> m (FinalizerPtr a) Source #

setUserFinaliser :: MonadIO m => Env -> RawValue p -> FinalizerPtr a -> m () Source #

vecGet :: MonadIO m => Env -> RawValue p -> CPtrdiff -> m (RawValue 'Regular) Source #

vecSet :: MonadIO m => Env -> RawValue p1 -> CPtrdiff -> RawValue p2 -> m () Source #

vecSize :: MonadIO m => Env -> RawValue p -> m CPtrdiff Source #

Expose functions to Emacs

exportToEmacs :: RawFunctionType o a -> IO (RawFunction o a) Source #

Take Haskell function and return C pointer to function (which ideally needs to be cleaned up later by freeHaskellFunPtrWrapped).

type RawFunctionType o a = Ptr Environment -> CPtrdiff -> Ptr (RawValue 'Regular) -> Ptr a -> IO (RawValue o) Source #

data RawFunction o a Source #

Pointer to a function that may later be called by by Emacs.

Instances

Instances details
Show (RawFunction o a) Source # 
Instance details

Defined in Data.Emacs.Module.Raw.Env.Internal

Methods

showsPrec :: Int -> RawFunction o a -> ShowS #

show :: RawFunction o a -> String #

showList :: [RawFunction o a] -> ShowS #

Eq (RawFunction o a) Source # 
Instance details

Defined in Data.Emacs.Module.Raw.Env.Internal

Methods

(==) :: RawFunction o a -> RawFunction o a -> Bool #

(/=) :: RawFunction o a -> RawFunction o a -> Bool #

Ord (RawFunction o a) Source # 
Instance details

Defined in Data.Emacs.Module.Raw.Env.Internal

Methods

compare :: RawFunction o a -> RawFunction o a -> Ordering #

(<) :: RawFunction o a -> RawFunction o a -> Bool #

(<=) :: RawFunction o a -> RawFunction o a -> Bool #

(>) :: RawFunction o a -> RawFunction o a -> Bool #

(>=) :: RawFunction o a -> RawFunction o a -> Bool #

max :: RawFunction o a -> RawFunction o a -> RawFunction o a #

min :: RawFunction o a -> RawFunction o a -> RawFunction o a #

Expose Haskell data to Emacs

freeStablePtrFinaliser :: FinalizerPtr a Source #

Pass to makeUserPtr so that Emacs will free the Haskell's stable pointer when the corresponding elisp value goes out of scope.