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

Data.Emacs.Module.Args

Description

 
Synopsis

Documentation

data Nat Source #

Type-level Peano numbers.

Indented to be used with DataKinds extension enabled.

Constructors

Z 
S Nat 

type family EmacsArgs (req :: Nat) (opt :: Nat) (rest :: Bool) (a :: Type) = (r :: Type) | r -> req opt rest a where ... Source #

Specification of the arguments that exposed functions can receive from Emacs.

This type family allows to declaratively specify how many required and optional arguments a function can take and whether it accepts rest arguments. It's a direct translation of argument lists in Emacs lisp, e.g.

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

The function above has 3 required arguments, 2 optional and also has rest arguments. The type family below has two Nats and one Bool to provide that info.

Equations

EmacsArgs ('S n) opt rest a = R a (EmacsArgs n opt rest a) 
EmacsArgs 'Z ('S k) rest a = O a (EmacsArgs 'Z k rest a) 
EmacsArgs 'Z 'Z 'True a = Rest a 
EmacsArgs 'Z 'Z 'False a = Stop a 

class EmacsInvocation req opt rest where Source #

Methods

supplyEmacsArgs :: MonadBase IO m => Int -> Ptr RawValue -> (RawValue -> m a) -> (EmacsArgs req opt rest a -> m b) -> m b Source #

Instances

Instances details
EmacsInvocation 'Z 'Z 'False Source # 
Instance details

Defined in Data.Emacs.Module.Args

Methods

supplyEmacsArgs :: MonadBase IO m => Int -> Ptr RawValue -> (RawValue -> m a) -> (EmacsArgs 'Z 'Z 'False a -> m b) -> m b Source #

EmacsInvocation 'Z 'Z 'True Source # 
Instance details

Defined in Data.Emacs.Module.Args

Methods

supplyEmacsArgs :: MonadBase IO m => Int -> Ptr RawValue -> (RawValue -> m a) -> (EmacsArgs 'Z 'Z 'True a -> m b) -> m b Source #

EmacsInvocation 'Z n rest => EmacsInvocation 'Z ('S n) rest Source # 
Instance details

Defined in Data.Emacs.Module.Args

Methods

supplyEmacsArgs :: MonadBase IO m => Int -> Ptr RawValue -> (RawValue -> m a) -> (EmacsArgs 'Z ('S n) rest a -> m b) -> m b Source #

EmacsInvocation n opt rest => EmacsInvocation ('S n) opt rest Source # 
Instance details

Defined in Data.Emacs.Module.Args

Methods

supplyEmacsArgs :: MonadBase IO m => Int -> Ptr RawValue -> (RawValue -> m a) -> (EmacsArgs ('S n) opt rest a -> m b) -> m b Source #

class GetArities (req :: Nat) (opt :: Nat) (rest :: Bool) where Source #

Helper to retrieve number of arguments a function takes for Emacs.

Methods

arities :: Proxy req -> Proxy opt -> Proxy rest -> (CPtrdiff, CPtrdiff) Source #

Instances

Instances details
NatValue req => GetArities req opt 'True Source # 
Instance details

Defined in Data.Emacs.Module.Args

Methods

arities :: Proxy req -> Proxy opt -> Proxy 'True -> (CPtrdiff, CPtrdiff) Source #

(NatValue req, NatValue opt) => GetArities req opt 'False Source # 
Instance details

Defined in Data.Emacs.Module.Args

Methods

arities :: Proxy req -> Proxy opt -> Proxy 'False -> (CPtrdiff, CPtrdiff) Source #

Argument inference

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