| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Futhark.TypeCheck
Contents
Description
The type checker checks whether the program is type-consistent.
Synopsis
- checkProg :: Checkable lore => Prog lore -> Either (TypeError lore) ()
- data TypeError lore = Error [String] (ErrorCase lore)
- data ErrorCase lore
- = TypeError String
- | UnexpectedType (Exp lore) Type [Type]
- | ReturnTypeError Name [ExtType] [ExtType]
- | DupDefinitionError Name
- | DupParamError Name VName
- | DupPatternError VName
- | InvalidPatternError (Pattern (Aliases lore)) [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 lore a
- bad :: ErrorCase lore -> TypeM lore a
- context :: String -> TypeM lore a -> TypeM lore a
- message :: Pretty a => String -> a -> String
- class (Attributes lore, CanBeAliased (Op lore)) => Checkable lore where
- checkExpLore :: ExpAttr lore -> TypeM lore ()
- checkBodyLore :: BodyAttr lore -> TypeM lore ()
- checkFParamLore :: VName -> FParamAttr lore -> TypeM lore ()
- checkLParamLore :: VName -> LParamAttr lore -> TypeM lore ()
- checkLetBoundLore :: VName -> LetAttr lore -> TypeM lore ()
- checkRetType :: [RetType lore] -> TypeM lore ()
- checkOp :: OpWithAliases (Op lore) -> TypeM lore ()
- matchPattern :: Pattern (Aliases lore) -> Exp (Aliases lore) -> TypeM lore ()
- primFParam :: VName -> PrimType -> TypeM lore (FParam (Aliases lore))
- primLParam :: VName -> PrimType -> TypeM lore (LParam (Aliases lore))
- matchReturnType :: [RetType lore] -> Result -> TypeM lore ()
- matchBranchType :: [BranchType lore] -> Body (Aliases lore) -> TypeM lore ()
- lookupVar :: VName -> TypeM lore (NameInfo (Aliases lore))
- lookupAliases :: Checkable lore => VName -> TypeM lore Names
- type Occurences = [Occurence]
- type UsageMap = Map VName [Usage]
- usageMap :: Occurences -> UsageMap
- collectOccurences :: TypeM lore a -> TypeM lore (a, Occurences)
- subCheck :: forall lore newlore a. (Checkable newlore, RetType lore ~ RetType newlore, LetAttr lore ~ LetAttr newlore, FParamAttr lore ~ FParamAttr newlore, LParamAttr lore ~ LParamAttr newlore) => TypeM newlore a -> TypeM lore a
- require :: Checkable lore => [Type] -> SubExp -> TypeM lore ()
- requireI :: Checkable lore => [Type] -> VName -> TypeM lore ()
- requirePrimExp :: Checkable lore => PrimType -> PrimExp VName -> TypeM lore ()
- checkSubExp :: Checkable lore => SubExp -> TypeM lore Type
- checkExp :: Checkable lore => Exp (Aliases lore) -> TypeM lore ()
- checkStms :: Checkable lore => Stms (Aliases lore) -> TypeM lore a -> TypeM lore a
- checkStm :: Checkable lore => Stm (Aliases lore) -> TypeM lore a -> TypeM lore a
- checkType :: Checkable lore => TypeBase Shape u -> TypeM lore ()
- checkExtType :: Checkable lore => TypeBase ExtShape u -> TypeM lore ()
- matchExtPattern :: Checkable lore => Pattern (Aliases lore) -> [ExtType] -> TypeM lore ()
- matchExtReturnType :: Checkable lore => [ExtType] -> Result -> TypeM lore ()
- matchExtBranchType :: Checkable lore => [ExtType] -> Body (Aliases lore) -> TypeM lore ()
- argType :: Arg -> Type
- argAliases :: Arg -> Names
- noArgAliases :: Arg -> Arg
- checkArg :: Checkable lore => SubExp -> TypeM lore Arg
- checkSOACArrayArgs :: Checkable lore => SubExp -> [VName] -> TypeM lore [Arg]
- checkLambda :: Checkable lore => Lambda (Aliases lore) -> [Arg] -> TypeM lore ()
- checkFun' :: Checkable lore => (Name, [DeclExtType], [(VName, NameInfo (Aliases lore))], BodyT (Aliases lore)) -> [(VName, Names)] -> TypeM lore () -> TypeM lore ()
- checkLambdaParams :: Checkable lore => [LParam lore] -> TypeM lore ()
- checkBody :: Checkable lore => Body (Aliases lore) -> TypeM lore ()
- checkLambdaBody :: Checkable lore => [Type] -> Body (Aliases lore) -> TypeM lore ()
- consume :: Names -> TypeM lore ()
- consumeOnlyParams :: [(VName, Names)] -> TypeM lore a -> TypeM lore a
- binding :: Checkable lore => Scope (Aliases lore) -> TypeM lore a -> TypeM lore a
Interface
checkProg :: Checkable lore => Prog lore -> Either (TypeError lore) () 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.
Constructors
Extensionality
The type checker runs in this monad.
context :: String -> TypeM lore a -> TypeM lore 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 (Attributes lore, CanBeAliased (Op lore)) => Checkable lore where Source #
The class of lores that can be type-checked.
Methods
checkExpLore :: ExpAttr lore -> TypeM lore () Source #
checkBodyLore :: BodyAttr lore -> TypeM lore () Source #
checkFParamLore :: VName -> FParamAttr lore -> TypeM lore () Source #
checkLParamLore :: VName -> LParamAttr lore -> TypeM lore () Source #
checkLetBoundLore :: VName -> LetAttr lore -> TypeM lore () Source #
checkRetType :: [RetType lore] -> TypeM lore () Source #
checkOp :: OpWithAliases (Op lore) -> TypeM lore () Source #
matchPattern :: Pattern (Aliases lore) -> Exp (Aliases lore) -> TypeM lore () Source #
primFParam :: VName -> PrimType -> TypeM lore (FParam (Aliases lore)) Source #
primLParam :: VName -> PrimType -> TypeM lore (LParam (Aliases lore)) Source #
matchReturnType :: [RetType lore] -> Result -> TypeM lore () Source #
matchBranchType :: [BranchType lore] -> Body (Aliases lore) -> TypeM lore () Source #
Instances
type Occurences = [Occurence] Source #
usageMap :: Occurences -> UsageMap Source #
collectOccurences :: TypeM lore a -> TypeM lore (a, Occurences) Source #
subCheck :: forall lore newlore a. (Checkable newlore, RetType lore ~ RetType newlore, LetAttr lore ~ LetAttr newlore, FParamAttr lore ~ FParamAttr newlore, LParamAttr lore ~ LParamAttr newlore) => TypeM newlore a -> TypeM lore a Source #
Checkers
require :: Checkable lore => [Type] -> SubExp -> TypeM lore () 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 lore => [Type] -> VName -> TypeM lore () Source #
Variant of require working on variable names.
argAliases :: Arg -> Names Source #
Remove all aliases from the Arg.
noArgAliases :: Arg -> Arg Source #
checkFun' :: Checkable lore => (Name, [DeclExtType], [(VName, NameInfo (Aliases lore))], BodyT (Aliases lore)) -> [(VName, Names)] -> TypeM lore () -> TypeM lore () Source #
consumeOnlyParams :: [(VName, Names)] -> TypeM lore a -> TypeM lore a Source #
Permit consumption of only the specified names. If one of these names is consumed, the consumption will be rewritten to be a consumption of the corresponding alias set. Consumption of anything else will result in a type error.