open-typerep-0.3.3: Open type representations and dynamic types

Safe HaskellNone
LanguageHaskell2010

Data.TypeRep.VarArg

Contents

Description

Utilities for polyvariadic functions

Synopsis

Working with polyvariadic functions

newtype Res a Source

Newtype marking the result of a N-ary function

Constructors

Res a 

type family ToRes a Source

Put a Res marker at the result type of a function

ToRes (a -> b -> ... -> x) = a -> b -> ... -> Res x

Equations

ToRes (a -> b) = a -> ToRes b 
ToRes a = Res a 

type family FromRes a Source

Remove the Res marker at the result type of a function

FromRes (a -> b -> ... -> Res x) = a -> b -> ... -> x

Equations

FromRes (a -> b) = a -> FromRes b 
FromRes (Res a) = a 

data Arity a where Source

Witness of the arity of a function. Arity will normally be indexed by (ToRes a).

Constructors

FunRes :: Arity (Res a) 
FunArg :: Arity b -> Arity (a -> b) 

class VarArg t where Source

Methods

aritySym :: VarArg u => t sig -> Args (AST u) sig -> Arity (ToRes (DenResult sig)) Source

fromResInvSym :: (VarArg u, a ~ DenResult sig) => t sig -> Args (AST u) sig -> Dict (FromRes (ToRes a) ~ a) Source

arity :: VarArg t => TypeRep t a -> Arity (ToRes a) Source

Get the Arity of a type. The purpose is to be able to distinguish between functions and non-functions without having to handle all cases of a TypeRep.

fromResInv :: VarArg t => TypeRep t a -> Dict (FromRes (ToRes a) ~ a) Source

Prove that FromRes is the inverse of ToRes

type NonFunction a = ToRes a ~ Res a Source

nonFunction :: (VarArg t, MonadError String m) => TypeRep t a -> m (Dict (NonFunction a)) Source

Attempt to prove that a type is not a function type

N-ary monadic functions

type family FunM m a Source

Give a function a monadic result type. (FunM m) will normally be indexed by (ToRes a).

FunM m (a -> b -> ... -> Res x) = a -> b -> ... -> m x

Equations

FunM m (a -> b) = a -> FunM m b 
FunM m (Res a) = m a 

liftMonadic :: forall t a m. (VarArg t, Monad m) => Proxy m -> TypeRep t a -> a -> FunM m (ToRes a) Source

Lift a function to a similar function with monadic result type

liftMonadic _ _ f = \a b ... x -> return (f a b ... x)

runMonadic :: forall t a m. VarArg t => (forall a. m a -> a) -> TypeRep t a -> FunM m (ToRes a) -> a Source

Run the result of a monadic function

runMonadic run _ f = \a b ... x -> run (f a b ... x)

compMonadic :: forall t a m1 m2. VarArg t => (forall a. m1 a -> m2 a) -> TypeRep t a -> FunM m1 (ToRes a) -> FunM m2 (ToRes a) Source

Compose a function with an N-ary monadic function

compMonadic f _ g = \a b ... x -> f (g a b ... x)

type family FunM2 m a Source

Give a function monadic arguments and result type. (FunM2 m) will normally be indexed by (ToRes a).

FunM m (a -> b -> ... -> Res x) = m a -> m b -> ... -> m x

Equations

FunM2 m (a -> b) = m a -> FunM2 m b 
FunM2 m (Res a) = m a 

liftMonadic2 :: forall t a m. (VarArg t, Monad m) => Proxy m -> TypeRep t a -> a -> FunM2 m (ToRes a) Source

Lift a function to a similar function with monadic arguments and result

liftMonadic f = \ma mb ... mx -> do
    a <- ma
    b <- mb
    ...
    x <- mx
    return (f a b ... x)