Safe Haskell | None |
---|---|
Language | Haskell98 |
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.
- data Config n = Config {
- configPrimKinds :: KindEnv n
- configPrimTypes :: TypeEnv n
- configPrimDataDefs :: DataDefs n
- configNameIsHole :: Maybe (n -> Bool)
- configTrackedEffects :: Bool
- configTrackedClosures :: Bool
- configFunctionalEffects :: Bool
- configFunctionalClosures :: Bool
- configEffectCapabilities :: Bool
- configGeneralLetRec :: Bool
- configImplicitRun :: Bool
- configImplicitBox :: Bool
- configOfProfile :: Profile n -> Config n
- data CheckTrace = CheckTrace {
- checkTraceDoc :: Doc
- checkModule :: (Show a, Ord n, Show n, Pretty n) => Config n -> Module a n -> Mode n -> (Either (Error a n) (Module (AnTEC a n) n), CheckTrace)
- checkType :: (Ord n, Show n, Pretty n) => Config n -> Universe -> Type n -> Either (Error a n) (Type n, Type n)
- checkTypeM :: (Ord n, Show n, Pretty n) => Config n -> Context n -> Universe -> Type n -> Mode n -> CheckM a n (Type n, Kind n, Context n)
- checkSpec :: (Ord n, Show n, Pretty n) => Config n -> Type n -> Either (Error a n) (Type n, Kind n)
- kindOfSpec :: (Ord n, Show n, Pretty n) => Config n -> Type n -> Either (Error a n) (Kind n)
- sortOfKind :: (Ord n, Show n, Pretty n) => Config n -> Kind n -> Either (Error a n) (Sort n)
- data Mode n
- data Demand
- checkExp :: (Show a, Ord n, Show n, Pretty n) => Config n -> EnvX n -> Mode n -> Demand -> Exp a n -> (Either (Error a n) (Exp (AnTEC a n) n, Type n, Effect n), CheckTrace)
- typeOfExp :: (Show a, Ord n, Pretty n, Show n) => Config n -> EnvX n -> Exp a n -> Either (Error a n) (Type n)
- checkWitness :: (Ord n, Show n, Pretty n) => Config n -> EnvX n -> Witness a n -> Either (Error a n) (Witness (AnT a n) n, Type n)
- typeOfWitness :: (Ord n, Show n, Pretty n) => Config n -> EnvX n -> Witness a n -> Either (Error a n) (Type n)
- typeOfWiCon :: WiCon n -> Type n
- takeSortOfKiCon :: KiCon -> Maybe (Sort n)
- kindOfTwCon :: TwCon -> Kind n
- kindOfTcCon :: TcCon -> Kind n
- data AnTEC a n = AnTEC {
- annotType :: Type n
- annotEffect :: Effect n
- annotClosure :: Closure n
- annotTail :: a
- data Error a n
- = ErrorType {
- errorTypeError :: ErrorType n
- | ErrorData { }
- | ErrorExportUndefined {
- errorName :: n
- | ErrorExportDuplicate {
- errorName :: n
- | ErrorExportMismatch {
- errorName :: n
- errorExportType :: Type n
- errorDefType :: Type n
- | ErrorImportDuplicate {
- errorName :: n
- | ErrorImportCapNotEffect {
- errorName :: n
- | ErrorImportValueNotData {
- errorName :: n
- | ErrorMismatch {
- errorAnnot :: a
- errorInferred :: Type n
- errorExpected :: Type n
- errorChecking :: Exp a n
- | ErrorUndefinedVar {
- errorAnnot :: a
- errorBound :: Bound n
- errorUniverse :: Universe
- | ErrorUndefinedCtor {
- errorAnnot :: a
- errorChecking :: Exp a n
- | ErrorAppMismatch {
- errrorAnnot :: a
- errorChecking :: Exp a n
- errorParamType :: Type n
- errorArgType :: Type n
- | ErrorAppNotFun {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorNotFunType :: Type n
- | ErrorAppCannotInferPolymorphic {
- errorAnnot :: a
- errorChecking :: Exp a n
- | ErrorLamShadow {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorBind :: Bind n
- | ErrorLamNotPure {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorUniverse :: Universe
- errorEffect :: Effect n
- | ErrorLamBindBadKind {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorType :: Type n
- errorKind :: Kind n
- | ErrorLamBodyNotData {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorBind :: Bind n
- errorType :: Type n
- errorKind :: Kind n
- | ErrorLamParamUnannotated {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorBind :: Bind n
- | ErrorLAMParamUnannotated {
- errorAnnot :: a
- errorChecking :: Exp a n
- | ErrorLAMParamBadSort {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorBind :: Bind n
- errorSort :: Sort n
- | ErrorLetMismatch {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorBind :: Bind n
- errorType :: Type n
- | ErrorLetBindingNotData {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorBind :: Bind n
- errorKind :: Kind n
- | ErrorLetBodyNotData {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorType :: Type n
- errorKind :: Kind n
- | ErrorLetrecBindingNotLambda {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorExp :: Exp a n
- | ErrorLetrecMissingAnnot {
- errorAnnot :: a
- errorBind :: Bind n
- errorExp :: Exp a n
- | ErrorLetrecRebound {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorBind :: Bind n
- | ErrorLetRegionsNotRegion {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorBinds :: [Bind n]
- errorKinds :: [Kind n]
- | ErrorLetRegionsRebound {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorBinds :: [Bind n]
- | ErrorLetRegionFree {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorBinds :: [Bind n]
- errorType :: Type n
- | ErrorLetRegionWitnessInvalid {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorBind :: Bind n
- | ErrorLetRegionWitnessConflict {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorBindWitness1 :: Bind n
- errorBindWitness2 :: Bind n
- | ErrorLetRegionsWitnessOther {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorBoundRegions :: [Bound n]
- errorBindWitness :: Bind n
- | ErrorWAppMismatch {
- errorAnnot :: a
- errorWitness :: Witness a n
- errorParamType :: Type n
- errorArgType :: Type n
- | ErrorWAppNotCtor {
- errorAnnot :: a
- errorWitness :: Witness a n
- errorNotFunType :: Type n
- errorArgType :: Type n
- | ErrorWitnessNotPurity {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorWitness :: Witness a n
- errorType :: Type n
- | ErrorCaseScrutineeNotAlgebraic {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorTypeScrutinee :: Type n
- | ErrorCaseScrutineeTypeUndeclared {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorTypeScrutinee :: Type n
- | ErrorCaseNoAlternatives {
- errorAnnot :: a
- errorChecking :: Exp a n
- | ErrorCaseNonExhaustive {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorCtorNamesMissing :: [n]
- | ErrorCaseNonExhaustiveLarge {
- errorAnnot :: a
- errorChecking :: Exp a n
- | ErrorCaseOverlapping {
- errorAnnot :: a
- errorChecking :: Exp a n
- | ErrorCaseTooManyBinders {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorCtorDaCon :: DaCon n (Type n)
- errorCtorFields :: Int
- errorPatternFields :: Int
- | ErrorCaseCannotInstantiate {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorTypeScrutinee :: Type n
- errorTypeCtor :: Type n
- | ErrorCaseScrutineeTypeMismatch {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorTypeScrutinee :: Type n
- errorTypePattern :: Type n
- | ErrorCaseFieldTypeMismatch {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorTypeAnnot :: Type n
- errorTypeField :: Type n
- | ErrorCaseAltResultMismatch {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorAltType1 :: Type n
- errorAltType2 :: Type n
- | ErrorWeakEffNotEff {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorEffect :: Effect n
- errorKind :: Kind n
- | ErrorRunNotSuspension {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorType :: Type n
- | ErrorRunNotSupported {
- errorAnnot :: a
- errorChecking :: Exp a n
- errorEffect :: Effect n
- | ErrorRunCannotInfer {
- errorAnnot :: a
- errorExp :: Exp a n
- | ErrorNakedType {
- errorAnnot :: a
- errorChecking :: Exp a n
- | ErrorNakedWitness {
- errorAnnot :: a
- errorChecking :: Exp a n
- = ErrorType {
- data ErrorType n
- = ErrorTypeUniverseMalfunction { }
- | ErrorTypeMismatch {
- errorTypeUniverse :: Universe
- errorTypeInferred :: Type n
- errorTypeExpected :: Type n
- errorTypeChecking :: Type n
- | ErrorTypeInfinite {
- errorTypeVar :: Type n
- errorTypeBind :: Type n
- | ErrorTypeUndefined {
- errorTypeBound :: Bound n
- | ErrorTypeUnappliedKindFun
- | ErrorTypeNakedSort {
- errorTypeSort :: Sort n
- | ErrorTypeUndefinedTypeCtor {
- errorTypeBound :: Bound n
- | ErrorTypeAppNotFun {
- errorTypeChecking :: Type n
- errorTypeFunType :: Type n
- errorTypeFunTypeKind :: Kind n
- errorTypeArgType :: Type n
- | ErrorTypeAppArgMismatch {
- errorTypeChecking :: Type n
- errorTypeFunType :: Type n
- errorTypeFunKind :: Kind n
- errorTypeArgType :: Type n
- errorTypeArgKind :: Kind n
- | ErrorTypeWitnessImplInvalid {
- errorTypeChecking :: Type n
- errorTypeLeftType :: Type n
- errorTypeLeftKind :: Kind n
- errorTypeRightType :: Type n
- errorTypeRightKind :: Kind n
- | ErrorTypeForallKindInvalid {
- errorTypeChecking :: Type n
- errorTypeBody :: Type n
- errorTypeKind :: Kind n
- | ErrorTypeSumKindMismatch {
- errorTypeKindExpected :: Kind n
- errorTypeTypeSum :: TypeSum n
- errorTypeKinds :: [Kind n]
- | ErrorTypeSumKindInvalid {
- errorTypeCheckingSum :: TypeSum n
- errorTypeKind :: Kind n
- data ErrorData n
- = ErrorDataDupTypeName {
- errorDataDupTypeName :: n
- | ErrorDataDupCtorName {
- errorDataCtorName :: n
- | ErrorDataWrongResult { }
- = ErrorDataDupTypeName {
Configuration
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
|
Instances
Checking Modules
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.
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
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. |
Demand placed on suspensions by the surrounding context.
Constructors
DemandRun | Run suspensions as we encounter them. |
DemandNone | Ignore suspensions, don't run them. |
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.
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
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.
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
The type checker adds this annotation to every node in the AST, giving its type, effect and closure.
Constructors
AnTEC | |
Fields
|
Error messages
All the things that can go wrong when type checking an expression or witness.
Constructors
ErrorType | Found a kind error when checking a type. |
Fields
| |
ErrorData | Found an error in the data type definitions. |
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. |
Fields
| |
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. |
Fields
| |
ErrorUndefinedVar | An undefined type variable. |
Fields
| |
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. |
Fields
| |
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. |
Fields
| |
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. |
Fields
| |
ErrorLetRegionsWitnessOther | A letregion-expression where a bound witnesses was not for the the region variable being introduced. |
Fields
| |
ErrorWAppMismatch | A witness application where the argument type does not match the parameter type. |
Fields
| |
ErrorWAppNotCtor | Tried to perform a witness application with a non-witness. |
Fields
| |
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. |
Fields
| |
ErrorCaseScrutineeTypeUndeclared | A case-expression where the scrutinee type is not in our set of data type declarations. |
Fields
| |
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. |
Fields
| |
ErrorCaseCannotInstantiate | A case-expression where the pattern types could not be instantiated with the arguments of the scrutinee type. |
Fields
| |
ErrorCaseScrutineeTypeMismatch | A case-expression where the type of the scrutinee does not match the type of the pattern. |
Fields
| |
ErrorCaseFieldTypeMismatch | A case-expression where the annotation on a pattern variable binder does not match the field type of the constructor. |
Fields
| |
ErrorCaseAltResultMismatch | A case-expression where the result types of the alternatives are not identical. |
Fields
| |
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 |
Fields
| |
ErrorNakedWitness | Found a naked |
Fields
|
Things that can go wrong when checking the kind of at type.
Constructors
Things that can go wrong when checking data type definitions.
Constructors
ErrorDataDupTypeName | A duplicate data type constructor name. |
Fields
| |
ErrorDataDupCtorName | A duplicate data constructor name. |
Fields
| |
ErrorDataWrongResult | A data constructor with the wrong result type. |
Fields |