{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE TypeOperators #-}
module Data.Emacs.Module.Args
( Nat(..)
, EmacsArgs
, EmacsInvocation(..)
, GetArities(..)
, R(..)
, O(..)
, Rest(..)
, Stop(..)
) where
import Control.Monad.Base
import Data.Kind
import Data.Proxy
import Foreign
import Foreign.C.Types (CPtrdiff)
import Data.Emacs.Module.Raw.Env (variadicFunctionArgs)
import Data.Emacs.Module.Raw.Value
data Nat = Z | S Nat
class NatValue (n :: Nat) where
natValue :: Proxy n -> Int
instance NatValue 'Z where
{-# INLINE natValue #-}
natValue _ = 0
instance forall n. NatValue n => NatValue ('S n) where
{-# INLINE natValue #-}
natValue _ = 1 + natValue (Proxy @n)
data R a b = R !a !b
data O a b = O !(Maybe a) !b
newtype Rest a = Rest [a]
data Stop a = Stop
type family EmacsArgs (req :: Nat) (opt :: Nat) (rest :: Bool) (a :: Type) = (r :: Type) | r -> req opt rest a where
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
supplyEmacsArgs
:: MonadBase IO m
=> Int
-> Ptr RawValue
-> (RawValue -> m a)
-> (EmacsArgs req opt rest a -> m b)
-> m b
instance EmacsInvocation 'Z 'Z 'False where
{-# INLINE supplyEmacsArgs #-}
supplyEmacsArgs _nargs _startPtr _mkInput f = f Stop
instance EmacsInvocation 'Z 'Z 'True where
{-# INLINE supplyEmacsArgs #-}
supplyEmacsArgs
:: MonadBase IO m
=> Int
-> Ptr RawValue
-> (RawValue -> m a)
-> (Rest a -> m b)
-> m b
supplyEmacsArgs nargs startPtr mkArg f =
case nargs of
0 -> f (Rest [])
n -> f . Rest =<< traverse mkArg =<< liftBase (peekArray n startPtr)
{-# INLINE advanceEmacsValuePtr #-}
advanceEmacsValuePtr :: Ptr RawValue -> Ptr RawValue
advanceEmacsValuePtr =
(`plusPtr` (sizeOf (undefined :: RawValue)))
instance EmacsInvocation 'Z n rest => EmacsInvocation 'Z ('S n) rest where
{-# INLINE supplyEmacsArgs #-}
supplyEmacsArgs
:: forall m a b. MonadBase IO m
=> Int
-> Ptr RawValue
-> (RawValue -> m a)
-> (O a (EmacsArgs 'Z n rest a) -> m b)
-> m b
supplyEmacsArgs nargs startPtr mkArg f =
case nargs of
0 -> supplyEmacsArgs nargs startPtr mkArg (f . O Nothing)
_ -> do
arg <- mkArg =<< liftBase (peek startPtr)
supplyEmacsArgs
(nargs - 1)
(advanceEmacsValuePtr startPtr)
mkArg
(f . O (Just arg))
instance EmacsInvocation n opt rest => EmacsInvocation ('S n) opt rest where
{-# INLINE supplyEmacsArgs #-}
supplyEmacsArgs
:: MonadBase IO m
=> Int
-> Ptr RawValue
-> (RawValue -> m a)
-> (R a (EmacsArgs n opt rest a) -> m b)
-> m b
supplyEmacsArgs nargs startPtr mkArg f = do
arg <- mkArg =<< liftBase (peek startPtr)
supplyEmacsArgs (nargs - 1) (advanceEmacsValuePtr startPtr) mkArg (f . R arg)
class GetArities (req :: Nat) (opt :: Nat) (rest :: Bool) where
arities :: Proxy req -> Proxy opt -> Proxy rest -> (CPtrdiff, CPtrdiff)
instance (NatValue req, NatValue opt) => GetArities req opt 'False where
{-# INLINE arities #-}
arities preq popt _ = (req, req + opt)
where
req = fromIntegral (natValue preq)
opt = fromIntegral (natValue popt)
instance NatValue req => GetArities req opt 'True where
{-# INLINE arities #-}
arities preq _ _ =
(fromIntegral (natValue preq), variadicFunctionArgs)