hypertypes-0.2.2: Typed ASTs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hyper.Syntax.Scheme

Description

Type schemes

Synopsis

Documentation

data Scheme varTypes typ h Source #

A type scheme representing a polymorphic type.

Constructors

Scheme 

Fields

Instances

Instances details
(HasInferredValue typ, UnifyGen m typ, HTraversable varTypes, HNodesConstraint varTypes (MonadInstantiate m), Infer m typ) => Infer m (Scheme varTypes typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

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 # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

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 # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

hzip :: forall (p :: HyperType) (q :: HyperType). (Scheme varTypes typ # p) -> (Scheme varTypes typ # q) -> Scheme varTypes typ # (p :*: q) Source #

HFoldable (Scheme varTypes typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

hfoldMap :: Monoid a => (forall (n :: HyperType). HWitness (Scheme varTypes typ) n -> (p # n) -> a) -> (Scheme varTypes typ # p) -> a Source #

HFunctor (Scheme varTypes typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

hmap :: (forall (n :: HyperType). HWitness (Scheme varTypes typ) n -> (p # n) -> q # n) -> (Scheme varTypes typ # p) -> Scheme varTypes typ # q Source #

HNodes (Scheme varTypes typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Associated Types

type HNodesConstraint (Scheme varTypes typ) c Source #

type HWitnessType (Scheme varTypes typ) :: HyperType -> Type Source #

Methods

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 # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

hpure :: (forall (n :: HyperType). HWitness (Scheme varTypes typ) n -> p # n) -> Scheme varTypes typ # p Source #

RNodes t => RNodes (Scheme v t) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

(HTraversable (Scheme v t), RTraversable t) => RTraversable (Scheme v t) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

HTraversable (Scheme varTypes typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

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 # 
Instance details

Defined in Hyper.Syntax.Scheme

Associated Types

type Rep (Scheme varTypes typ h) :: Type -> Type #

Methods

from :: Scheme varTypes typ h -> Rep (Scheme varTypes typ h) x #

to :: Rep (Scheme varTypes typ h) x -> Scheme varTypes typ h #

Constraints (Scheme varTypes typ h) Show => Show (Scheme varTypes typ h) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

showsPrec :: Int -> Scheme varTypes typ h -> ShowS #

show :: Scheme varTypes typ h -> String #

showList :: [Scheme varTypes typ h] -> ShowS #

Constraints (Scheme varTypes typ h) Binary => Binary (Scheme varTypes typ h) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

put :: Scheme varTypes typ h -> Put #

get :: Get (Scheme varTypes typ h) #

putList :: [Scheme varTypes typ h] -> Put #

Constraints (Scheme varTypes typ h) NFData => NFData (Scheme varTypes typ h) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

rnf :: Scheme varTypes typ h -> () #

Constraints (Scheme varTypes typ h) Eq => Eq (Scheme varTypes typ h) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

(==) :: Scheme varTypes typ h -> Scheme varTypes typ h -> Bool #

(/=) :: Scheme varTypes typ h -> Scheme varTypes typ h -> Bool #

Constraints (Scheme varTypes typ h) Ord => Ord (Scheme varTypes typ h) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

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 # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

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 # 
Instance details

Defined in Hyper.Syntax.Scheme

type InferOf (Scheme _1 t) = HFlip GTerm t
type HWitnessType (Scheme varTypes typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

type HWitnessType (Scheme varTypes typ) = W_Scheme varTypes typ
type HNodesConstraint (Scheme varTypes typ) constraint Source # 
Instance details

Defined in Hyper.Syntax.Scheme

type HNodesConstraint (Scheme varTypes typ) constraint = constraint typ
type Rep (Scheme varTypes typ h) Source # 
Instance details

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 #

Constructors

W_Scheme_typ :: W_Scheme varTypes typ typ 

newtype QVars typ Source #

Constructors

QVars (Map (QVar (GetHyperType typ)) (TypeConstraintsOf (GetHyperType typ))) 

Instances

Instances details
(Ord (QVar (GetHyperType typ)), Semigroup (TypeConstraintsOf (GetHyperType typ))) => Monoid (QVars typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

mempty :: QVars typ #

mappend :: QVars typ -> QVars typ -> QVars typ #

mconcat :: [QVars typ] -> QVars typ #

(Ord (QVar (GetHyperType typ)), Semigroup (TypeConstraintsOf (GetHyperType typ))) => Semigroup (QVars typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

(<>) :: QVars typ -> QVars typ -> QVars typ #

sconcat :: NonEmpty (QVars typ) -> QVars typ #

stimes :: Integral b => b -> QVars typ -> QVars typ #

Generic (QVars typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Associated Types

type Rep (QVars typ) :: Type -> Type #

Methods

from :: QVars typ -> Rep (QVars typ) x #

to :: Rep (QVars typ) x -> QVars typ #

Constraints (QVars typ) Show => Show (QVars typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

showsPrec :: Int -> QVars typ -> ShowS #

show :: QVars typ -> String #

showList :: [QVars typ] -> ShowS #

Constraints (QVars typ) Binary => Binary (QVars typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

put :: QVars typ -> Put #

get :: Get (QVars typ) #

putList :: [QVars typ] -> Put #

Constraints (QVars typ) NFData => NFData (QVars typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

rnf :: QVars typ -> () #

Constraints (QVars typ) Eq => Eq (QVars typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

(==) :: QVars typ -> QVars typ -> Bool #

(/=) :: QVars typ -> QVars typ -> Bool #

Constraints (QVars typ) Ord => Ord (QVars typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

compare :: QVars typ -> QVars typ -> Ordering #

(<) :: QVars typ -> QVars typ -> Bool #

(<=) :: QVars typ -> QVars typ -> Bool #

(>) :: QVars typ -> QVars typ -> Bool #

(>=) :: QVars typ -> QVars typ -> Bool #

max :: QVars typ -> QVars typ -> QVars typ #

min :: QVars typ -> QVars typ -> QVars typ #

Ord (QVar (GetHyperType typ)) => At (QVars typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

at :: Index (QVars typ) -> Lens' (QVars typ) (Maybe (IxValue (QVars typ))) #

Ord (QVar (GetHyperType typ)) => Ixed (QVars typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

ix :: Index (QVars typ) -> Traversal' (QVars typ) (IxValue (QVars typ)) #

(Pretty (TypeConstraintsOf typ), Pretty (QVar typ)) => Pretty (QVars # typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

pPrintPrec :: PrettyLevel -> Rational -> (QVars # typ) -> Doc #

pPrint :: (QVars # typ) -> Doc #

pPrintList :: PrettyLevel -> [QVars # typ] -> Doc #

type Rep (QVars typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

type Rep (QVars typ) = D1 ('MetaData "QVars" "Hyper.Syntax.Scheme" "hypertypes-0.2.2-9g9pX7Hb2mGI4yyssTDpOd" 'True) (C1 ('MetaCons "QVars" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (QVar (GetHyperType typ)) (TypeConstraintsOf (GetHyperType typ))))))
type Index (QVars typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

type Index (QVars typ) = QVar (GetHyperType typ)
type IxValue (QVars typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

_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 #

Minimal complete definition

Nothing

Methods

hasSchemeRecursive :: Proxy varTypes -> Proxy m -> RecMethod (HasScheme varTypes m) t Source #

default hasSchemeRecursive :: HNodesConstraint t (HasScheme varTypes m) => Proxy varTypes -> Proxy m -> RecMethod (HasScheme varTypes m) t Source #

Instances

Instances details
Recursive (HasScheme varTypes m) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

recurse :: forall (h :: HyperType) proxy. (HNodes h, HasScheme varTypes m h) => proxy (HasScheme varTypes m h) -> Dict (HNodesConstraint h (HasScheme varTypes m)) Source #

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 #

Methods

localInstantiations :: (QVarInstances (UVarOf m) # t) -> m a -> m a Source #

lookupQVar :: QVar t -> m (UVarOf m # t) Source #

newtype QVarInstances h typ Source #

Constructors

QVarInstances (Map (QVar (GetHyperType typ)) (h typ)) 

Instances

Instances details
Generic (QVarInstances h typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Associated Types

type Rep (QVarInstances h typ) :: Type -> Type #

Methods

from :: QVarInstances h typ -> Rep (QVarInstances h typ) x #

to :: Rep (QVarInstances h typ) x -> QVarInstances h typ #

Constraints (QVarInstances h typ) Show => Show (QVarInstances h typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

showsPrec :: Int -> QVarInstances h typ -> ShowS #

show :: QVarInstances h typ -> String #

showList :: [QVarInstances h typ] -> ShowS #

Constraints (QVarInstances h typ) Binary => Binary (QVarInstances h typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

put :: QVarInstances h typ -> Put #

get :: Get (QVarInstances h typ) #

putList :: [QVarInstances h typ] -> Put #

Constraints (QVarInstances h typ) NFData => NFData (QVarInstances h typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

rnf :: QVarInstances h typ -> () #

Constraints (QVarInstances h typ) Eq => Eq (QVarInstances h typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

(==) :: QVarInstances h typ -> QVarInstances h typ -> Bool #

(/=) :: QVarInstances h typ -> QVarInstances h typ -> Bool #

Constraints (QVarInstances h typ) Ord => Ord (QVarInstances h typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

Methods

compare :: QVarInstances h typ -> QVarInstances h typ -> Ordering #

(<) :: QVarInstances h typ -> QVarInstances h typ -> Bool #

(<=) :: QVarInstances h typ -> QVarInstances h typ -> Bool #

(>) :: QVarInstances h typ -> QVarInstances h typ -> Bool #

(>=) :: QVarInstances h typ -> QVarInstances h typ -> Bool #

max :: QVarInstances h typ -> QVarInstances h typ -> QVarInstances h typ #

min :: QVarInstances h typ -> QVarInstances h typ -> QVarInstances h typ #

type Rep (QVarInstances h typ) Source # 
Instance details

Defined in Hyper.Syntax.Scheme

type Rep (QVarInstances h typ) = D1 ('MetaData "QVarInstances" "Hyper.Syntax.Scheme" "hypertypes-0.2.2-9g9pX7Hb2mGI4yyssTDpOd" 'True) (C1 ('MetaCons "QVarInstances" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (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)) Source #

makeQVarInstances :: Unify m typ => (QVars # typ) -> m (QVarInstances (UVarOf m) # typ) Source #