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

Safe HaskellNone
LanguageHaskell2010

Language.Syntactic.TypeRep

Description

Utilities for working with ASTs of the form AST (sym :&: TypeRep t)

Synopsis

Documentation

mkLamSym :: Witness Typeable t t => TypeRep t a -> TypeRep t b -> Name -> BindingT (b :-> Full (a -> b)) Source

injTR :: (sub :<: sup, Typeable t (DenResult sig)) => sub sig -> AST (sup :&: TypeRep t) sig Source

Inject a symbol in an AST with a domain decorated by a type representation

smartSymTR :: (Signature sig, supT ~ (sup :&: TypeRep t), f ~ SmartFun supT sig, sig ~ SmartSig f, supT ~ SmartSym f, sub :<: sup, Typeable t (DenResult sig)) => sub sig -> f Source

Make a smart constructor of a symbol. smartSymT has any type of the form:

smartSymTR :: (sub :<: AST (sup :&: TypeRep t), Typeable t x)
    => sub (a :-> b :-> ... :-> Full x)
    -> (ASTF sup a -> ASTF sup b -> ... -> ASTF sup x)

sugarSymTR :: (Signature sig, supT ~ (sup :&: TypeRep t), fi ~ SmartFun supT sig, sig ~ SmartSig fi, supT ~ SmartSym fi, SyntacticN f fi, sub :<: sup, Typeable t (DenResult sig)) => sub sig -> f Source

"Sugared" symbol application

sugarSymTR has any type of the form:

sugarSymTR ::
    ( sub :<: AST (sup :&: TypeRep t)
    , Syntactic a
    , Syntactic b
    , ...
    , Syntactic x
    , Domain a ~ Domain b ~ ... ~ Domain x
    , Typeable t (Internal x)
    ) => sub (Internal a :-> Internal b :-> ... :-> Full (Internal x))
      -> (a -> b -> ... -> x)

defaultInterfaceTypeRep Source

Arguments

:: (BindingT :<: sym, Let :<: sym, symT ~ (sym :&: TypeRep t), FunType :<: t, TypeEq t t, Witness Typeable t t) 
=> (forall a b. ASTF symT a -> ASTF symT b -> Bool)

Can the expression represented by the first argument be shared in the second argument?

-> (forall a. ASTF symT a -> Bool)

Can we hoist over this expression?

-> CodeMotionInterface symT 

Default CodeMotionInterface for domains of the form ((... :+: BindingT :+: ... ) :&: TypeRep t)