Copyright | (c) Sergey Vinokurov 2018 |
---|---|
License | Apache-2.0 (see LICENSE) |
Maintainer | serg.foo@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Nat
- type family EmacsArgs (req :: Nat) (opt :: Nat) (rest :: Bool) (a :: Type) = (r :: Type) | r -> req opt rest a where ...
- class EmacsInvocation req opt rest where
- class GetArities (req :: Nat) (opt :: Nat) (rest :: Bool) where
- data R a b = R !a !b
- data O a b = O !(Maybe a) !b
- newtype Rest a = Rest [a]
- data Stop a = Stop
Documentation
Type-level Peano numbers.
Indented to be used with DataKinds
extension enabled.
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 Nat
s and one Bool
to provide that info.
class EmacsInvocation req opt rest where Source #
supplyEmacsArgs :: MonadBase IO m => Int -> Ptr RawValue -> (RawValue -> m a) -> (EmacsArgs req opt rest a -> m b) -> m b Source #
Instances
EmacsInvocation 'Z 'Z 'False Source # | |
EmacsInvocation 'Z 'Z 'True Source # | |
EmacsInvocation 'Z n rest => EmacsInvocation 'Z ('S n) rest Source # | |
EmacsInvocation n opt rest => EmacsInvocation ('S n) opt rest Source # | |
class GetArities (req :: Nat) (opt :: Nat) (rest :: Bool) where Source #
Helper to retrieve number of arguments a function takes for Emacs.
Instances
NatValue req => GetArities req opt 'True Source # | |
(NatValue req, NatValue opt) => GetArities req opt 'False Source # | |