Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
The type checker checks whether the program is type-consistent.
Synopsis
- checkProg :: Checkable rep => Prog (Aliases rep) -> Either (TypeError rep) ()
- data TypeError rep = Error [Text] (ErrorCase rep)
- data ErrorCase rep
- = TypeError Text
- | UnexpectedType (Exp rep) Type [Type]
- | ReturnTypeError Name [ExtType] [ExtType]
- | DupDefinitionError Name
- | DupParamError Name VName
- | DupPatError VName
- | InvalidPatError (Pat (LetDec (Aliases rep))) [ExtType] (Maybe String)
- | UnknownVariableError VName
- | UnknownFunctionError Name
- | ParameterMismatch (Maybe Name) [Type] [Type]
- | SlicingError Int Int
- | BadAnnotation String Type Type
- | ReturnAliased Name VName
- | UniqueReturnAliased Name
- | NotAnArray VName Type
- | PermutationError [Int] Int (Maybe VName)
- data TypeM rep a
- bad :: ErrorCase rep -> TypeM rep a
- context :: Text -> TypeM rep a -> TypeM rep a
- class (AliasableRep rep, TypedOp (OpC rep)) => Checkable rep where
- checkExpDec :: ExpDec rep -> TypeM rep ()
- checkBodyDec :: BodyDec rep -> TypeM rep ()
- checkFParamDec :: VName -> FParamInfo rep -> TypeM rep ()
- checkLParamDec :: VName -> LParamInfo rep -> TypeM rep ()
- checkLetBoundDec :: VName -> LetDec rep -> TypeM rep ()
- checkRetType :: [RetType rep] -> TypeM rep ()
- matchPat :: Pat (LetDec (Aliases rep)) -> Exp (Aliases rep) -> TypeM rep ()
- primFParam :: VName -> PrimType -> TypeM rep (FParam (Aliases rep))
- matchReturnType :: [RetType rep] -> Result -> TypeM rep ()
- matchBranchType :: [BranchType rep] -> Body (Aliases rep) -> TypeM rep ()
- matchLoopResult :: [FParam (Aliases rep)] -> Result -> TypeM rep ()
- checkOp :: Op (Aliases rep) -> TypeM rep ()
- lookupVar :: VName -> TypeM rep (NameInfo (Aliases rep))
- lookupAliases :: Checkable rep => VName -> TypeM rep Names
- checkOpWith :: (Op (Aliases rep) -> TypeM rep ()) -> TypeM rep a -> TypeM rep a
- require :: Checkable rep => [Type] -> SubExp -> TypeM rep ()
- requireI :: Checkable rep => [Type] -> VName -> TypeM rep ()
- requirePrimExp :: Checkable rep => PrimType -> PrimExp VName -> TypeM rep ()
- checkSubExp :: Checkable rep => SubExp -> TypeM rep Type
- checkCerts :: Checkable rep => Certs -> TypeM rep ()
- checkExp :: Checkable rep => Exp (Aliases rep) -> TypeM rep ()
- checkStms :: Checkable rep => Stms (Aliases rep) -> TypeM rep a -> TypeM rep a
- checkStm :: Checkable rep => Stm (Aliases rep) -> TypeM rep a -> TypeM rep a
- checkSlice :: Checkable rep => Type -> Slice SubExp -> TypeM rep ()
- checkType :: Checkable rep => TypeBase Shape u -> TypeM rep ()
- checkExtType :: Checkable rep => TypeBase ExtShape u -> TypeM rep ()
- matchExtPat :: Checkable rep => Pat (LetDec (Aliases rep)) -> [ExtType] -> TypeM rep ()
- matchExtBranchType :: Checkable rep => [ExtType] -> Body (Aliases rep) -> TypeM rep ()
- argType :: Arg -> Type
- noArgAliases :: Arg -> Arg
- checkArg :: Checkable rep => SubExp -> TypeM rep Arg
- checkSOACArrayArgs :: Checkable rep => SubExp -> [VName] -> TypeM rep [Arg]
- checkLambda :: Checkable rep => Lambda (Aliases rep) -> [Arg] -> TypeM rep ()
- checkBody :: Checkable rep => Body (Aliases rep) -> TypeM rep [Names]
- consume :: Checkable rep => Names -> TypeM rep ()
- binding :: Checkable rep => Scope (Aliases rep) -> TypeM rep a -> TypeM rep a
- alternative :: TypeM rep a -> TypeM rep b -> TypeM rep (a, b)
Interface
checkProg :: Checkable rep => Prog (Aliases rep) -> Either (TypeError rep) () Source #
Type check a program containing arbitrary type information, yielding either a type error or a program with complete type information.
A type error.
Information about an error during type checking. The Show
instance for this type produces a human-readable description.
Extensionality
The type checker runs in this monad.
context :: Text -> TypeM rep a -> TypeM rep a Source #
Add information about what is being type-checked to the current
context. Liberal use of this combinator makes it easier to track
type errors, as the strings are added to type errors signalled via
bad
.
class (AliasableRep rep, TypedOp (OpC rep)) => Checkable rep where Source #
The class of representations that can be type-checked.
checkExpDec :: ExpDec rep -> TypeM rep () Source #
checkBodyDec :: BodyDec rep -> TypeM rep () Source #
checkFParamDec :: VName -> FParamInfo rep -> TypeM rep () Source #
default checkFParamDec :: FParamInfo rep ~ DeclType => VName -> FParamInfo rep -> TypeM rep () Source #
checkLParamDec :: VName -> LParamInfo rep -> TypeM rep () Source #
default checkLParamDec :: LParamInfo rep ~ Type => VName -> LParamInfo rep -> TypeM rep () Source #
checkLetBoundDec :: VName -> LetDec rep -> TypeM rep () Source #
checkRetType :: [RetType rep] -> TypeM rep () Source #
default checkRetType :: RetType rep ~ DeclExtType => [RetType rep] -> TypeM rep () Source #
matchPat :: Pat (LetDec (Aliases rep)) -> Exp (Aliases rep) -> TypeM rep () Source #
primFParam :: VName -> PrimType -> TypeM rep (FParam (Aliases rep)) Source #
default primFParam :: FParamInfo rep ~ DeclType => VName -> PrimType -> TypeM rep (FParam (Aliases rep)) Source #
matchReturnType :: [RetType rep] -> Result -> TypeM rep () Source #
default matchReturnType :: RetType rep ~ DeclExtType => [RetType rep] -> Result -> TypeM rep () Source #
matchBranchType :: [BranchType rep] -> Body (Aliases rep) -> TypeM rep () Source #
default matchBranchType :: BranchType rep ~ ExtType => [BranchType rep] -> Body (Aliases rep) -> TypeM rep () Source #
matchLoopResult :: [FParam (Aliases rep)] -> Result -> TypeM rep () Source #
default matchLoopResult :: FParamInfo rep ~ DeclType => [FParam (Aliases rep)] -> Result -> TypeM rep () Source #
checkOp :: Op (Aliases rep) -> TypeM rep () Source #
Used at top level; can be locally changed with checkOpWith
.
Instances
Checkers
require :: Checkable rep => [Type] -> SubExp -> TypeM rep () Source #
require ts se
causes a '(TypeError vn)' if the type of se
is
not a subtype of one of the types in ts
.
requireI :: Checkable rep => [Type] -> VName -> TypeM rep () Source #
Variant of require
working on variable names.
checkSlice :: Checkable rep => Type -> Slice SubExp -> TypeM rep () Source #
Check a slicing operation of an array of the provided type.
noArgAliases :: Arg -> Arg Source #