| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Hyper.Class.Infer.InferOf
Synopsis
- class HasInferredType t where
- class HasInferredValue t where
- inferredValue :: Lens' (InferOf t # v) (v # t)
- class InferOfConstraint c h where
- inferOfConstraint :: proxy0 c -> proxy1 h -> Dict (c (InferOf h))
- class (HTraversable (InferOf h), Recursively (InferOfConstraint HFunctor) h, Recursively (InferOfConstraint HFoldable) h) => RTraversableInferOf h
Documentation
class HasInferredType t where Source #
HasInferredType t represents that InferOf t contains a TypeOf t, which represents its inferred type.
class HasInferredValue t where Source #
HasInferredValue t represents that InferOf t contains an inferred value for t.
class InferOfConstraint c h where Source #
Methods
inferOfConstraint :: proxy0 c -> proxy1 h -> Dict (c (InferOf h)) Source #
Instances
| c (InferOf h) => InferOfConstraint c h Source # | |
Defined in Hyper.Class.Infer.InferOf Methods inferOfConstraint :: proxy0 c -> proxy1 h -> Dict (c (InferOf h)) Source # | |
class (HTraversable (InferOf h), Recursively (InferOfConstraint HFunctor) h, Recursively (InferOfConstraint HFoldable) h) => RTraversableInferOf h Source #
Instances
| Recursive RTraversableInferOf Source # | |
Defined in Hyper.Class.Infer.InferOf Methods recurse :: forall (h :: HyperType) proxy. (HNodes h, RTraversableInferOf h) => proxy (RTraversableInferOf h) -> Dict (HNodesConstraint h RTraversableInferOf) Source # | |
| (RTraversable t, RTraversableInferOf t) => RTraversableInferOf (Scheme v t) Source # | |
Defined in Hyper.Type.AST.Scheme Methods rTraversableInferOfRec :: Proxy (Scheme v t) -> Dict (HNodesConstraint (Scheme v t) RTraversableInferOf) | |