ddc-core-0.4.3.1: Disciplined Disciple Compiler core language and type checker.

Safe HaskellNone
LanguageHaskell98

DDC.Core.Check

Contents

Description

Type checker for the Disciple Core language.

The functions in this module do not check for language fragment compliance. This needs to be done separately via DDC.Core.Fragment.

Synopsis

Configuration

data Config n Source #

Static configuration for the type checker. These fields don't change as we decend into the tree.

The starting configuration should be converted from the profile that defines the language fragment you are checking. See DDC.Core.Fragment and use configOfProfile below.

Constructors

Config 

Fields

configOfProfile :: Profile n -> Config n Source #

Convert a language profile to a type checker configuration.

Type checker trace

data CheckTrace Source #

Human readable trace of the type checker.

Constructors

CheckTrace 

Fields

Checking Modules

checkModule Source #

Arguments

:: (Show a, Ord n, Show n, Pretty n) 
=> Config n

Static configuration.

-> Module a n

Module to check.

-> Mode n

Type checker mode.

-> (Either (Error a n) (Module (AnTEC a n) n), CheckTrace) 

Type check a module.

If it's good, you get a new version with types attached to all the bound variables

If it's bad, you get a description of the error.

Checking Types

checkType :: (Ord n, Show n, Pretty n) => Config n -> Universe -> Type n -> Either (Error a n) (Type n, Type n) Source #

Check a type in the given universe with the given environment Returns the updated type and its classifier (a kind or sort), depeding on the universe of the type being checked.

checkTypeM Source #

Arguments

:: (Ord n, Show n, Pretty n) 
=> Config n

Type checker configuration.

-> Context n

Context of type to check.

-> Universe

What universe the type to check is in.

-> Type n

The type to check (can be a Spec or Kind)

-> Mode n

Type checker mode.

-> CheckM a n (Type n, Kind n, Context n) 

Check a type returning its kind, or a kind returning its sort.

The unverse of the thing to check is directly specified, and if the thing is not actually in this universe they you'll get an error.

We track what universe the provided kind is in for defence against transform bugs. Types like ([a : [b : Data]. b]. a -> a), should not be accepted by the source parser, but may be created by bogus program transformations. Quantifiers cannot be used at the kind level, so it's better to fail early.

checkSpec :: (Ord n, Show n, Pretty n) => Config n -> Type n -> Either (Error a n) (Type n, Kind n) Source #

Check a spec in the given environment, returning an error or its kind.

kindOfSpec :: (Ord n, Show n, Pretty n) => Config n -> Type n -> Either (Error a n) (Kind n) Source #

Check a spec in an empty environment, returning an error or its kind.

sortOfKind :: (Ord n, Show n, Pretty n) => Config n -> Kind n -> Either (Error a n) (Sort n) Source #

Check a kind in an empty environment, returning an error or its sort.

Checking Expressions

data Mode n Source #

What mode we're performing type checking/inference in.

Constructors

Recon

Reconstruct the type of the expression, requiring type annotations on parameters as well as type applications to already be present.

Synth [Exists n]

The ascending smoke of incense.

Synthesise the type of the expression, producing unification variables for bidirectional type inference.

Any new unification variables introduced may be used to define the given existentials, so the need to be declared outside their scopes. If the list is empty we can add new variables to the inner most scope.

Check (Type n)

The descending tongue of flame. Check the type of an expression against this expected type, and unify expected types into unification variables for bidirecional type inference.

Instances

Eq n => Eq (Mode n) Source # 

Methods

(==) :: Mode n -> Mode n -> Bool #

(/=) :: Mode n -> Mode n -> Bool #

Show n => Show (Mode n) Source # 

Methods

showsPrec :: Int -> Mode n -> ShowS #

show :: Mode n -> String #

showList :: [Mode n] -> ShowS #

(Eq n, Pretty n) => Pretty (Mode n) Source # 

Associated Types

data PrettyMode (Mode n) :: * Source #

Methods

pprDefaultMode :: PrettyMode (Mode n) Source #

ppr :: Mode n -> Doc Source #

pprPrec :: Int -> Mode n -> Doc Source #

pprModePrec :: PrettyMode (Mode n) -> Int -> Mode n -> Doc Source #

data Demand Source #

Demand placed on suspensions by the surrounding context.

Constructors

DemandRun

Run suspensions as we encounter them.

DemandNone

Ignore suspensions, don't run them.

checkExp Source #

Arguments

:: (Show a, Ord n, Show n, Pretty n) 
=> Config n

Static configuration.

-> EnvX n

Environment of expression.

-> Mode n

Check mode.

-> Demand

Demand placed on the expression.

-> Exp a n

Expression to check.

-> (Either (Error a n) (Exp (AnTEC a n) n, Type n, Effect n), CheckTrace) 

Type check an expression.

If it's good, you get a new version with types attached every AST node, as well as every binding occurrence of a variable.

If it's bad, you get a description of the error.

The kinds and types of primitives are added to the environments automatically, you don't need to supply these as part of the starting kind and type environment.

typeOfExp Source #

Arguments

:: (Show a, Ord n, Pretty n, Show n) 
=> Config n

Static configuration.

-> EnvX n

Environment of expresion.

-> Exp a n

Expression to check.

-> Either (Error a n) (Type n) 

Like checkExp, but only return the value type of an expression.

Checking Witnesses

checkWitness Source #

Arguments

:: (Ord n, Show n, Pretty n) 
=> Config n

Type checker configuration.

-> EnvX n

Type checker environment.

-> Witness a n

Witness to check.

-> Either (Error a n) (Witness (AnT a n) n, Type n) 

Check a witness.

If it's good, you get a new version with types attached to all the bound variables, as well as the type of the overall witness.

If it's bad, you get a description of the error.

The returned expression has types attached to all variable occurrences, so you can call typeOfWitness on any open subterm.

The kinds and types of primitives are added to the environments automatically, you don't need to supply these as part of the starting environments.

typeOfWitness Source #

Arguments

:: (Ord n, Show n, Pretty n) 
=> Config n

Type checker configuration.

-> EnvX n

Type checker environment.

-> Witness a n

Witness to check.

-> Either (Error a n) (Type n) 

Like checkWitness, but check in an empty environment.

As this function is not given an environment, the types of free variables must be attached directly to the bound occurrences. This attachment is performed by checkWitness above.

typeOfWiCon :: WiCon n -> Type n Source #

Take the type of a witness constructor.

Kinds of Constructors

takeSortOfKiCon :: KiCon -> Maybe (Sort n) Source #

Take the superkind of an atomic kind constructor.

Yields Nothing for the kind function (~>) as it doesn't have a sort without being fully applied.

kindOfTwCon :: TwCon -> Kind n Source #

Take the kind of a witness type constructor.

kindOfTcCon :: TcCon -> Kind n Source #

Take the kind of a computation type constructor.

Annotations

data AnTEC a n Source #

The type checker adds this annotation to every node in the AST, giving its type, effect and closure.

Constructors

AnTEC 

Instances

(Show a, Show n) => Show (AnTEC a n) Source # 

Methods

showsPrec :: Int -> AnTEC a n -> ShowS #

show :: AnTEC a n -> String #

showList :: [AnTEC a n] -> ShowS #

(NFData a, NFData n) => NFData (AnTEC a n) Source # 

Methods

rnf :: AnTEC a n -> () #

Pretty (AnTEC a n) Source # 

Associated Types

data PrettyMode (AnTEC a n) :: * Source #

Methods

pprDefaultMode :: PrettyMode (AnTEC a n) Source #

ppr :: AnTEC a n -> Doc Source #

pprPrec :: Int -> AnTEC a n -> Doc Source #

pprModePrec :: PrettyMode (AnTEC a n) -> Int -> AnTEC a n -> Doc Source #

Error messages

data Error a n Source #

All the things that can go wrong when type checking an expression or witness.

Constructors

ErrorType

Found a kind error when checking a type.

ErrorData

Found an error in the data type definitions.

Fields

ErrorExportUndefined

Exported value is undefined.

Fields

ErrorExportDuplicate

Exported name is exported multiple times.

Fields

ErrorExportMismatch

Type signature of exported binding does not match the type at the definition site.

ErrorImportDuplicate

Imported name is imported multiple times.

Fields

ErrorImportCapNotEffect

An imported capability that does not have kind Effect.

Fields

ErrorImportValueNotData

An imported value that doesn't have kind Data.

Fields

ErrorMismatch

Generic mismatch between expected and inferred types.

ErrorUndefinedVar

An undefined type variable.

ErrorUndefinedCtor

A data constructor that wasn't in the set of data definitions.

Fields

ErrorAppMismatch

A function application where the parameter and argument don't match.

ErrorAppNotFun

Tried to apply something that is not a function.

Fields

ErrorAppCannotInferPolymorphic

Cannot infer type of polymorphic expression.

Fields

ErrorLamShadow

A type abstraction that tries to shadow a type variable that is already in the environment.

Fields

ErrorLamNotPure

An abstraction where the body has a visible side effect that is not supported by the current language fragment.

ErrorLamBindBadKind

A value function where the parameter does not have data or witness kind.

Fields

ErrorLamBodyNotData

An abstraction where the body does not have data kind.

Fields

ErrorLamParamUnannotated

A function abstraction without a type annotation on the parameter.

Fields

ErrorLAMParamUnannotated

A type abstraction without a kind annotation on the parameter.

Fields

ErrorLAMParamBadSort

A type abstraction parameter with a bad sort.

Fields

ErrorLetMismatch

A let-expression where the type of the binder does not match the right of the binding.

Fields

ErrorLetBindingNotData

A let-expression where the right of the binding does not have data kind.

Fields

ErrorLetBodyNotData

A let-expression where the body does not have data kind.

Fields

ErrorLetrecBindingNotLambda

A recursive let-expression where the right of the binding is not a lambda abstraction.

Fields

ErrorLetrecMissingAnnot

A recursive let-binding with a missing type annotation.

Fields

ErrorLetrecRebound

A recursive let-expression that has more than one binding with the same name.

Fields

ErrorLetRegionsNotRegion

A letregion-expression where the some of the bound variables do not have region kind.

Fields

ErrorLetRegionsRebound

A letregion-expression that tried to shadow some pre-existing named region variables.

Fields

ErrorLetRegionFree

A letregion-expression where some of the the bound region variables are free in the type of the body.

Fields

ErrorLetRegionWitnessInvalid

A letregion-expression that tried to create a witness with an invalid type.

Fields

ErrorLetRegionWitnessConflict

A letregion-expression that tried to create conflicting witnesses.

ErrorLetRegionsWitnessOther

A letregion-expression where a bound witnesses was not for the the region variable being introduced.

ErrorWAppMismatch

A witness application where the argument type does not match the parameter type.

ErrorWAppNotCtor

Tried to perform a witness application with a non-witness.

ErrorWitnessNotPurity

A witness provided for a purify cast that does not witness purity.

Fields

ErrorCaseScrutineeNotAlgebraic

A case-expression where the scrutinee type is not algebraic.

ErrorCaseScrutineeTypeUndeclared

A case-expression where the scrutinee type is not in our set of data type declarations.

ErrorCaseNoAlternatives

A case-expression with no alternatives.

Fields

ErrorCaseNonExhaustive

A case-expression where the alternatives don't cover all the possible data constructors.

Fields

ErrorCaseNonExhaustiveLarge

A case-expression where the alternatives don't cover all the possible constructors, and the type has too many data constructors to list.

Fields

ErrorCaseOverlapping

A case-expression with overlapping alternatives.

Fields

ErrorCaseTooManyBinders

A case-expression where one of the patterns has too many binders.

ErrorCaseCannotInstantiate

A case-expression where the pattern types could not be instantiated with the arguments of the scrutinee type.

ErrorCaseScrutineeTypeMismatch

A case-expression where the type of the scrutinee does not match the type of the pattern.

ErrorCaseFieldTypeMismatch

A case-expression where the annotation on a pattern variable binder does not match the field type of the constructor.

ErrorCaseAltResultMismatch

A case-expression where the result types of the alternatives are not identical.

ErrorWeakEffNotEff

A weakeff-cast where the type provided does not have effect kind.

Fields

ErrorRunNotSuspension

A run cast applied to a non-suspension.

Fields

ErrorRunNotSupported

A run cast where the context does not support the suspended effect.

Fields

ErrorRunCannotInfer

A run cast where we cannot infer the type of the suspended computation and thus cannot check if its effects are suppored by the context.

Fields

ErrorNakedType

Found a naked XType that wasn't the argument of an application.

Fields

ErrorNakedWitness

Found a naked XWitness that wasn't the argument of an application.

Fields

Instances

(Show a, Show n) => Show (Error a n) Source # 

Methods

showsPrec :: Int -> Error a n -> ShowS #

show :: Error a n -> String #

showList :: [Error a n] -> ShowS #

data ErrorType n Source #

Things that can go wrong when checking the kind of at type.

Constructors

ErrorTypeUniverseMalfunction

Tried to check a type using the wrong universe, for example: asking for the kind of a kind.

ErrorTypeMismatch

Generic kind mismatch.

ErrorTypeInfinite

Cannot construct infinite type.

Fields

ErrorTypeUndefined

An undefined type variable.

Fields

ErrorTypeUnappliedKindFun

Found an unapplied kind function constructor.

ErrorTypeNakedSort

Found a naked sort constructor.

Fields

ErrorTypeUndefinedTypeCtor

An undefined type constructor.

Fields

ErrorTypeAppNotFun

A type application where the thing being applied is not a function.

ErrorTypeAppArgMismatch

A type application where the parameter and argument kinds don't match.

ErrorTypeWitnessImplInvalid

A witness implication where the premise or conclusion has an invalid kind.

ErrorTypeForallKindInvalid

A forall where the body does not have data or witness kind.

ErrorTypeSumKindMismatch

A type sum where the components have differing kinds.

ErrorTypeSumKindInvalid

A type sum that does not have effect or closure kind.

Instances

data ErrorData n Source #

Things that can go wrong when checking data type definitions.

Constructors

ErrorDataDupTypeName

A duplicate data type constructor name.

ErrorDataDupCtorName

A duplicate data constructor name.

Fields

ErrorDataWrongResult

A data constructor with the wrong result type.

Instances