hypertypes-0.2.2: Typed ASTs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hyper.Unify.Generalize

Description

Generalization of type schemes

Synopsis

Documentation

generalize :: forall m t. UnifyGen m t => (UVarOf m # t) -> m (GTerm (UVarOf m) # t) Source #

Generalize a unification term pointed by the given variable to a GTerm. Unification variables that are scoped within the term become universally quantified skolems.

instantiate :: UnifyGen m t => (GTerm (UVarOf m) # t) -> m (UVarOf m # t) Source #

Instantiate a generalized type with fresh unification variables for the quantified variables

data GTerm v ast Source #

An efficient representation of a type scheme arising from generalizing a unification term. Type subexpressions which are completely monomoprhic are tagged as such, to avoid redundant instantation and unification work

Constructors

GMono (v ast)

Completely monomoprhic term

GPoly (v ast)

Points to a quantified variable (instantiation will create fresh unification terms) (USkolem or UResolved)

GBody (ast :# GTerm v)

Term with some polymorphic parts

Instances

Instances details
HFoldable v => HFoldable (GTerm v) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (GTerm v) n -> (p # n) -> a) -> (GTerm v # p) -> a Source #

HFunctor v => HFunctor (GTerm v) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Methods

hmap :: (forall (n :: HyperType). HWitness (GTerm v) n -> (p # n) -> q # n) -> (GTerm v # p) -> GTerm v # q Source #

HNodes v => HNodes (GTerm v) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Associated Types

type HNodesConstraint (GTerm v) c Source #

type HWitnessType (GTerm v) :: HyperType -> Type Source #

Methods

hLiftConstraint :: forall c (n :: HyperType) r. HNodesConstraint (GTerm v) c => HWitness (GTerm v) n -> Proxy c -> (c n => r) -> r Source #

HTraversable v => HTraversable (GTerm v) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Methods

hsequence :: forall f (p :: AHyperType -> Type). Applicative f => (GTerm v # ContainedH f p) -> f (GTerm v # p) Source #

Generic (GTerm v ast) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Associated Types

type Rep (GTerm v ast) :: Type -> Type #

Methods

from :: GTerm v ast -> Rep (GTerm v ast) x #

to :: Rep (GTerm v ast) x -> GTerm v ast #

Constraints (GTerm v ast) Show => Show (GTerm v ast) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Methods

showsPrec :: Int -> GTerm v ast -> ShowS #

show :: GTerm v ast -> String #

showList :: [GTerm v ast] -> ShowS #

Constraints (GTerm v ast) Binary => Binary (GTerm v ast) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Methods

put :: GTerm v ast -> Put #

get :: Get (GTerm v ast) #

putList :: [GTerm v ast] -> Put #

Constraints (GTerm v ast) NFData => NFData (GTerm v ast) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Methods

rnf :: GTerm v ast -> () #

Constraints (GTerm v ast) Eq => Eq (GTerm v ast) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Methods

(==) :: GTerm v ast -> GTerm v ast -> Bool #

(/=) :: GTerm v ast -> GTerm v ast -> Bool #

Constraints (GTerm v ast) Ord => Ord (GTerm v ast) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Methods

compare :: GTerm v ast -> GTerm v ast -> Ordering #

(<) :: GTerm v ast -> GTerm v ast -> Bool #

(<=) :: GTerm v ast -> GTerm v ast -> Bool #

(>) :: GTerm v ast -> GTerm v ast -> Bool #

(>=) :: GTerm v ast -> GTerm v ast -> Bool #

max :: GTerm v ast -> GTerm v ast -> GTerm v ast #

min :: GTerm v ast -> GTerm v ast -> GTerm v ast #

Recursively HFoldable ast => HFoldable (HFlip GTerm ast) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (HFlip GTerm ast) n -> (p # n) -> a) -> (HFlip GTerm ast # p) -> a Source #

Recursively HFunctor ast => HFunctor (HFlip GTerm ast) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Methods

hmap :: (forall (n :: HyperType). HWitness (HFlip GTerm ast) n -> (p # n) -> q # n) -> (HFlip GTerm ast # p) -> HFlip GTerm ast # q Source #

RNodes a => HNodes (HFlip GTerm a) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Associated Types

type HNodesConstraint (HFlip GTerm a) c Source #

type HWitnessType (HFlip GTerm a) :: HyperType -> Type Source #

Methods

hLiftConstraint :: forall c (n :: HyperType) r. HNodesConstraint (HFlip GTerm a) c => HWitness (HFlip GTerm a) n -> Proxy c -> (c n => r) -> r Source #

RTraversable ast => HTraversable (HFlip GTerm ast) Source # 
Instance details

Defined in Hyper.Unify.Generalize

Methods

hsequence :: forall f (p :: AHyperType -> Type). Applicative f => (HFlip GTerm ast # ContainedH f p) -> f (HFlip GTerm ast # p) Source #

type HWitnessType (GTerm v) Source # 
Instance details

Defined in Hyper.Unify.Generalize

type HNodesConstraint (GTerm v) constraint Source # 
Instance details

Defined in Hyper.Unify.Generalize

type HNodesConstraint (GTerm v) constraint = (HNodesConstraint v constraint, constraint (GTerm v))
type Rep (GTerm v ast) Source # 
Instance details

Defined in Hyper.Unify.Generalize

type Rep (GTerm v ast) = D1 ('MetaData "GTerm" "Hyper.Unify.Generalize" "hypertypes-0.2.2-9g9pX7Hb2mGI4yyssTDpOd" 'False) (C1 ('MetaCons "GMono" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (v ast))) :+: (C1 ('MetaCons "GPoly" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (v ast))) :+: C1 ('MetaCons "GBody" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ast :# GTerm v)))))
type HWitnessType (HFlip GTerm a) Source # 
Instance details

Defined in Hyper.Unify.Generalize

type HNodesConstraint (HFlip GTerm a) c Source # 
Instance details

Defined in Hyper.Unify.Generalize

type HNodesConstraint (HFlip GTerm a) c = (c a, Recursive c)

_GMono :: forall v ast. Prism' (GTerm v ast) (v ast) Source #

_GPoly :: forall v ast. Prism' (GTerm v ast) (v ast) Source #

_GBody :: forall v ast. Prism' (GTerm v ast) ((:#) ast (GTerm v)) Source #

data W_GTerm (v :: AHyperType -> Type) node where Source #

Constructors

W_GTerm_GTerm_v :: W_GTerm v (GTerm v) 
E_GTerm_v :: (HWitness v node) -> W_GTerm v node 

instantiateWith :: forall m t a. UnifyGen m t => m a -> (forall n. TypeConstraintsOf n -> UTerm (UVarOf m) # n) -> (GTerm (UVarOf m) # t) -> m (UVarOf m # t, a) Source #

instantiateForAll :: forall m t. UnifyGen m t => (TypeConstraintsOf t -> UTerm (UVarOf m) # t) -> (UVarOf m # t) -> WriterT [m ()] m (UVarOf m # t) Source #

Exports for SPECIALIZE pragmas.

instantiateH :: forall m t. UnifyGen m t => (forall n. TypeConstraintsOf n -> UTerm (UVarOf m) # n) -> (GTerm (UVarOf m) # t) -> WriterT [m ()] m (UVarOf m # t) Source #