Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Type schemes
Synopsis
- data Scheme varTypes typ h = Scheme {}
- sForAlls :: forall varTypes typ h varTypes. Lens (Scheme varTypes typ h) (Scheme varTypes typ h) ((#) varTypes QVars) ((#) varTypes QVars)
- sTyp :: forall varTypes typ h typ h. Lens (Scheme varTypes typ h) (Scheme varTypes typ h) ((:#) h typ) ((:#) h typ)
- data W_Scheme (varTypes :: AHyperType -> Type) (typ :: HyperType) node where
- W_Scheme_typ :: W_Scheme varTypes typ typ
- newtype QVars typ = QVars (Map (QVar (GetHyperType typ)) (TypeConstraintsOf (GetHyperType typ)))
- _QVars :: forall typ typ. Iso (QVars typ) (QVars typ) (Map (QVar (GetHyperType typ)) (TypeConstraintsOf (GetHyperType typ))) (Map (QVar (GetHyperType typ)) (TypeConstraintsOf (GetHyperType typ)))
- class (UnifyGen m t, HNodeLens varTypes t, Ord (QVar t)) => HasScheme varTypes m t where
- hasSchemeRecursive :: Proxy varTypes -> Proxy m -> RecMethod (HasScheme varTypes m) t
- loadScheme :: forall m varTypes typ. (HTraversable varTypes, HNodesConstraint varTypes (UnifyGen m), HasScheme varTypes m typ) => (Pure # Scheme varTypes typ) -> m (GTerm (UVarOf m) # typ)
- saveScheme :: (HNodesConstraint varTypes OrdQVar, HPointed varTypes, HasScheme varTypes m typ) => (GTerm (UVarOf m) # typ) -> m (Pure # Scheme varTypes typ)
- class UnifyGen m t => MonadInstantiate m t where
- localInstantiations :: (QVarInstances (UVarOf m) # t) -> m a -> m a
- lookupQVar :: QVar t -> m (UVarOf m # t)
- inferType :: (InferOf t ~ ANode t, HNodesConstraint t HasInferredValue, MonadInstantiate m t) => (t # InferChild m h) -> m (t # h, InferOf t # UVarOf m)
- newtype QVarInstances h typ = QVarInstances (Map (QVar (GetHyperType typ)) (h typ))
- _QVarInstances :: forall h typ h typ. Iso (QVarInstances h typ) (QVarInstances h typ) (Map (QVar (GetHyperType typ)) (h typ)) (Map (QVar (GetHyperType typ)) (h typ))
- makeQVarInstances :: Unify m typ => (QVars # typ) -> m (QVarInstances (UVarOf m) # typ)
Documentation
data Scheme varTypes typ h Source #
A type scheme representing a polymorphic type.
Instances
(HasInferredValue typ, UnifyGen m typ, HTraversable varTypes, HNodesConstraint varTypes (MonadInstantiate m), Infer m typ) => Infer m (Scheme varTypes typ) Source # | |
Defined in Hyper.Syntax.Scheme inferBody :: forall (h :: AHyperType -> Type). (Scheme varTypes typ # InferChild m h) -> m (Scheme varTypes typ # h, InferOf (Scheme varTypes typ) # UVarOf m) Source # inferContext :: proxy0 m -> proxy1 (Scheme varTypes typ) -> Dict (HNodesConstraint (Scheme varTypes typ) (Infer m), HNodesConstraint (InferOf (Scheme varTypes typ)) (UnifyGen m)) Source # | |
(c (Scheme v t), Recursively c t) => Recursively c (Scheme v t) Source # | |
Defined in Hyper.Syntax.Scheme recursively :: proxy (c (Scheme v t)) -> Dict (c (Scheme v t), HNodesConstraint (Scheme v t) (Recursively c)) Source # | |
Semigroup (varTypes # QVars) => HApply (Scheme varTypes typ) Source # | |
HFoldable (Scheme varTypes typ) Source # | |
HFunctor (Scheme varTypes typ) Source # | |
HNodes (Scheme varTypes typ) Source # | |
Defined in Hyper.Syntax.Scheme type HNodesConstraint (Scheme varTypes typ) c Source # type HWitnessType (Scheme varTypes typ) :: HyperType -> Type Source # hLiftConstraint :: forall c (n :: HyperType) r. HNodesConstraint (Scheme varTypes typ) c => HWitness (Scheme varTypes typ) n -> Proxy c -> (c n => r) -> r Source # | |
Monoid (varTypes # QVars) => HPointed (Scheme varTypes typ) Source # | |
RNodes t => RNodes (Scheme v t) Source # | |
Defined in Hyper.Syntax.Scheme | |
(HTraversable (Scheme v t), RTraversable t) => RTraversable (Scheme v t) Source # | |
Defined in Hyper.Syntax.Scheme recursiveHTraversable :: RecMethod RTraversable (Scheme v t) Source # | |
HTraversable (Scheme varTypes typ) Source # | |
Defined in Hyper.Syntax.Scheme hsequence :: forall f (p :: AHyperType -> Type). Applicative f => (Scheme varTypes typ # ContainedH f p) -> f (Scheme varTypes typ # p) Source # | |
Generic (Scheme varTypes typ h) Source # | |
Constraints (Scheme varTypes typ h) Show => Show (Scheme varTypes typ h) Source # | |
Constraints (Scheme varTypes typ h) Binary => Binary (Scheme varTypes typ h) Source # | |
Constraints (Scheme varTypes typ h) NFData => NFData (Scheme varTypes typ h) Source # | |
Defined in Hyper.Syntax.Scheme | |
Constraints (Scheme varTypes typ h) Eq => Eq (Scheme varTypes typ h) Source # | |
Constraints (Scheme varTypes typ h) Ord => Ord (Scheme varTypes typ h) Source # | |
Defined in Hyper.Syntax.Scheme compare :: Scheme varTypes typ h -> Scheme varTypes typ h -> Ordering # (<) :: Scheme varTypes typ h -> Scheme varTypes typ h -> Bool # (<=) :: Scheme varTypes typ h -> Scheme varTypes typ h -> Bool # (>) :: Scheme varTypes typ h -> Scheme varTypes typ h -> Bool # (>=) :: Scheme varTypes typ h -> Scheme varTypes typ h -> Bool # max :: Scheme varTypes typ h -> Scheme varTypes typ h -> Scheme varTypes typ h # min :: Scheme varTypes typ h -> Scheme varTypes typ h -> Scheme varTypes typ h # | |
(Pretty (varTypes # QVars), Pretty (h :# typ)) => Pretty (Scheme varTypes typ h) Source # | |
Defined in Hyper.Syntax.Scheme pPrintPrec :: PrettyLevel -> Rational -> Scheme varTypes typ h -> Doc # pPrint :: Scheme varTypes typ h -> Doc # pPrintList :: PrettyLevel -> [Scheme varTypes typ h] -> Doc # | |
type InferOf (Scheme _1 t) Source # | |
Defined in Hyper.Syntax.Scheme | |
type HWitnessType (Scheme varTypes typ) Source # | |
Defined in Hyper.Syntax.Scheme | |
type HNodesConstraint (Scheme varTypes typ) constraint Source # | |
Defined in Hyper.Syntax.Scheme | |
type Rep (Scheme varTypes typ h) Source # | |
Defined in Hyper.Syntax.Scheme type Rep (Scheme varTypes typ h) = D1 ('MetaData "Scheme" "Hyper.Syntax.Scheme" "hypertypes-0.2.2-9g9pX7Hb2mGI4yyssTDpOd" 'False) (C1 ('MetaCons "Scheme" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sForAlls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (varTypes # QVars)) :*: S1 ('MetaSel ('Just "_sTyp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (h :# typ)))) |
sForAlls :: forall varTypes typ h varTypes. Lens (Scheme varTypes typ h) (Scheme varTypes typ h) ((#) varTypes QVars) ((#) varTypes QVars) Source #
sTyp :: forall varTypes typ h typ h. Lens (Scheme varTypes typ h) (Scheme varTypes typ h) ((:#) h typ) ((:#) h typ) Source #
data W_Scheme (varTypes :: AHyperType -> Type) (typ :: HyperType) node where Source #
W_Scheme_typ :: W_Scheme varTypes typ typ |
QVars (Map (QVar (GetHyperType typ)) (TypeConstraintsOf (GetHyperType typ))) |
Instances
_QVars :: forall typ typ. Iso (QVars typ) (QVars typ) (Map (QVar (GetHyperType typ)) (TypeConstraintsOf (GetHyperType typ))) (Map (QVar (GetHyperType typ)) (TypeConstraintsOf (GetHyperType typ))) Source #
class (UnifyGen m t, HNodeLens varTypes t, Ord (QVar t)) => HasScheme varTypes m t where Source #
Nothing
loadScheme :: forall m varTypes typ. (HTraversable varTypes, HNodesConstraint varTypes (UnifyGen m), HasScheme varTypes m typ) => (Pure # Scheme varTypes typ) -> m (GTerm (UVarOf m) # typ) Source #
Load scheme into unification monad so that different instantiations share the scheme's monomorphic parts - their unification is O(1) as it is the same shared unification term.
saveScheme :: (HNodesConstraint varTypes OrdQVar, HPointed varTypes, HasScheme varTypes m typ) => (GTerm (UVarOf m) # typ) -> m (Pure # Scheme varTypes typ) Source #
class UnifyGen m t => MonadInstantiate m t where Source #
localInstantiations :: (QVarInstances (UVarOf m) # t) -> m a -> m a Source #
inferType :: (InferOf t ~ ANode t, HNodesConstraint t HasInferredValue, MonadInstantiate m t) => (t # InferChild m h) -> m (t # h, InferOf t # UVarOf m) Source #
newtype QVarInstances h typ Source #
QVarInstances (Map (QVar (GetHyperType typ)) (h typ)) |
Instances
_QVarInstances :: forall h typ h typ. Iso (QVarInstances h typ) (QVarInstances h typ) (Map (QVar (GetHyperType typ)) (h typ)) (Map (QVar (GetHyperType typ)) (h typ)) Source #
makeQVarInstances :: Unify m typ => (QVars # typ) -> m (QVarInstances (UVarOf m) # typ) Source #