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

Safe HaskellNone
LanguageHaskell2010

Data.TypeRep.TH

Synopsis

Documentation

deriveRender_forType Source

Arguments

:: Name

Type name

-> DecsQ 

A version of deriveRender that applies typeName to each constructor name. That is, e.g. the constructor Int_t :: IntType (Full Int) will be rendered as "Int".

deriveTypeEq Source

Arguments

:: Name

Type name

-> DecsQ 

Derive TypeEq instance for a type representation

deriveWitness Source

Arguments

:: Name

Class name

-> Name

Type name

-> DecsQ 

Derive Witness instance for a type representation

instance Witness Cl t t => Witness Cl Ty t where
  witSym Con1 Nil = Dict
  witSym Con2 (a :* b :* Nil) =
      case wit (Proxy :: Proxy Cl) (TypeRep a) of
        Dict -> case wit (Proxy :: Proxy Cl) (TypeRep b) of
          Dict -> Dict

derivePWitness Source

Arguments

:: Name

Class name

-> Name

Type name

-> DecsQ 

Derive PWitness instance for a type representation

instance PWitness Cl t t => PWitness Cl Ty t where
  pwitSym Con1 Nil = return Dict
  pwitSym Con2 (a :* b :* Nil) = do
      Dict <- pwit (Proxy :: Proxy Cl) (TypeRep a)
      Dict <- pwit (Proxy :: Proxy Cl) (TypeRep b)
      return Dict

deriveWitnessAny Source

Arguments

:: Name

Type name

-> DecsQ 

Derive Witness Any instance for a type representation

instance Witness Any Ty t where
  witSym _ _ = Dict
  witSym _ _ = Dict

derivePWitnessAny Source

Arguments

:: Name

Type name

-> DecsQ 

Derive PWitness Any instance for a type representation

instance PWitness Any Ty t where
  pwitSym _ _ = return Dict
  pwitSym _ _ = return Dict

deriveWitnessTypeable Source

Arguments

:: Name

Type name

-> DecsQ 

Derive Witness (Typeable Ty) instance for a type representation

instance (Ty :<: t) => Witness (Typeable t) Ty t where
  witSym Con1 Nil = Dict
  witSym Con2 (a :* b :* Nil) =
      case wit (Proxy :: Proxy (Typeable t)) (TypeRep a) of
        Dict -> case wit (Proxy :: Proxy (Typeable t)) (TypeRep b) of
          Dict -> Dict

derivePWitnessTypeable Source

Arguments

:: Name

Type name

-> DecsQ 

Derive PWitness (Typeable Ty) instance for a type representation

instance (Ty :<: t) => PWitness (Typeable t) Ty t where
  pwitSym Con1 Nil = return Dict
  pwitSym Con2 (a :* b :* Nil) = do
      Dict <- pwit (Proxy :: Proxy (Typeable t)) (TypeRep a)
      Dict <- pwit (Proxy :: Proxy (Typeable t)) (TypeRep b)
      return Dict