| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Hyper.Class.Infer
Synopsis
- type family InferOf (t :: HyperType) :: HyperType
- class (Monad m, HFunctor t) => Infer m t where
- inferBody :: (t # InferChild m h) -> m (t # h, InferOf t # UVarOf m)
- inferContext :: proxy0 m -> proxy1 t -> Dict (HNodesConstraint t (Infer m), HNodesConstraint (InferOf t) (UnifyGen m))
- newtype InferChild m h t = InferChild {
- inferChild :: m (InferredChild (UVarOf m) h t)
- _InferChild :: forall m h t m h t. Iso (InferChild m h t) (InferChild m h t) (m (InferredChild (UVarOf m) h t)) (m (InferredChild (UVarOf m) h t))
- data InferredChild v h t = InferredChild {
- _inRep :: !(h t)
- _inType :: !(InferOf (GetHyperType t) # v)
- inType :: forall v h t v. Lens (InferredChild v h t) (InferredChild v h t) ((#) (InferOf (GetHyperType t)) v) ((#) (InferOf (GetHyperType t)) v)
- inRep :: forall v h t h. Lens (InferredChild v h t) (InferredChild v h t) (h t) (h t)
Documentation
type family InferOf (t :: HyperType) :: HyperType Source #
InferOf e is the inference result of e.
Most commonly it is an inferred type, using
type instance InferOf MyTerm = ANode MyType
But it may also be other things, for example:
- An inferred value (for types inside terms)
- An inferred type together with a scope
Instances
| type InferOf (App e) Source # | |
Defined in Hyper.Type.AST.App | |
| type InferOf (Rec1 h) Source # | |
Defined in Hyper.Class.Infer | |
| type InferOf (HCompose Prune t) Source # | |
Defined in Hyper.Type.Prune | |
| type InferOf (Var _1 t) Source # | |
Defined in Hyper.Type.AST.Var | |
| type InferOf (Scheme _1 t) Source # | |
Defined in Hyper.Type.AST.Scheme | |
| type InferOf (TypeSig _1 t) Source # | |
Defined in Hyper.Type.AST.TypeSig | |
| type InferOf (FromNom _1 e) Source # | |
Defined in Hyper.Type.AST.Nominal | |
| type InferOf (ToNom n e) Source # | |
Defined in Hyper.Type.AST.Nominal | |
| type InferOf (Let _1 e) Source # | |
Defined in Hyper.Type.AST.Let | |
| type InferOf (Lam _1 t) Source # | |
Defined in Hyper.Type.AST.Lam | |
| type InferOf (a :+: _1) Source # | |
Defined in Hyper.Class.Infer | |
| type InferOf (TypedLam _1 _2 e) Source # | |
Defined in Hyper.Type.AST.TypedLam | |
| type InferOf (M1 _1 _2 h) Source # | |
Defined in Hyper.Class.Infer | |
class (Monad m, HFunctor t) => Infer m t where Source #
Infer m t enables infer to perform type-inference for t in the Monad m.
The inferContext method represents the following constraints on t:
HNodesConstraint (InferOf t) (Unify m)- The child nodes of the inferrence can unify in themMonadHNodesConstraint t (Infer m)-Infer mis also available for child nodes
It replaces context for the Infer class to avoid UndecidableSuperClasses.
Instances usually don't need to implement this method as the default implementation works for them,
but infinitely polymorphic trees such as Scope do need to implement the method,
because the required context is infinite.
Minimal complete definition
Nothing
Methods
inferBody :: (t # InferChild m h) -> m (t # h, InferOf t # UVarOf m) Source #
Infer the body of an expression given the inference actions for its child nodes.
default inferBody :: (Generic1 t, Infer m (Rep1 t), InferOf t ~ InferOf (Rep1 t)) => (t # InferChild m h) -> m (t # h, InferOf t # UVarOf m) Source #
inferContext :: proxy0 m -> proxy1 t -> Dict (HNodesConstraint t (Infer m), HNodesConstraint (InferOf t) (UnifyGen m)) Source #
default inferContext :: (HNodesConstraint t (Infer m), HNodesConstraint (InferOf t) (UnifyGen m)) => proxy0 m -> proxy1 t -> Dict (HNodesConstraint t (Infer m), HNodesConstraint (InferOf t) (UnifyGen m)) Source #
Instances
newtype InferChild m h t Source #
A HyperType containing an inference action.
The caller may modify the scope before invoking the action via
localScopeType or localLevel
Constructors
| InferChild | |
Fields
| |
_InferChild :: forall m h t m h t. Iso (InferChild m h t) (InferChild m h t) (m (InferredChild (UVarOf m) h t)) (m (InferredChild (UVarOf m) h t)) Source #
data InferredChild v h t Source #
A HyperType containing an inferred child node
Constructors
| InferredChild | |
Fields | |
inType :: forall v h t v. Lens (InferredChild v h t) (InferredChild v h t) ((#) (InferOf (GetHyperType t)) v) ((#) (InferOf (GetHyperType t)) v) Source #
inRep :: forall v h t h. Lens (InferredChild v h t) (InferredChild v h t) (h t) (h t) Source #