futhark-0.9.1: An optimising compiler for a functional, array-oriented language.

Safe HaskellNone
LanguageHaskell2010

Futhark.TypeCheck

Contents

Description

The type checker checks whether the program is type-consistent.

Synopsis

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.

data TypeError lore Source #

A type error.

Constructors

Error [String] (ErrorCase lore) 
Instances
Checkable lore => Show (TypeError lore) Source # 
Instance details

Defined in Futhark.TypeCheck

Methods

showsPrec :: Int -> TypeError lore -> ShowS #

show :: TypeError lore -> String #

showList :: [TypeError lore] -> ShowS #

Extensionality

data TypeM lore a Source #

The type checker runs in this monad.

Instances
MonadState Names (TypeM lore) Source # 
Instance details

Defined in Futhark.TypeCheck

Methods

get :: TypeM lore Names #

put :: Names -> TypeM lore () #

state :: (Names -> (a, Names)) -> TypeM lore a #

Monad (TypeM lore) Source # 
Instance details

Defined in Futhark.TypeCheck

Methods

(>>=) :: TypeM lore a -> (a -> TypeM lore b) -> TypeM lore b #

(>>) :: TypeM lore a -> TypeM lore b -> TypeM lore b #

return :: a -> TypeM lore a #

fail :: String -> TypeM lore a #

Functor (TypeM lore) Source # 
Instance details

Defined in Futhark.TypeCheck

Methods

fmap :: (a -> b) -> TypeM lore a -> TypeM lore b #

(<$) :: a -> TypeM lore b -> TypeM lore a #

Applicative (TypeM lore) Source # 
Instance details

Defined in Futhark.TypeCheck

Methods

pure :: a -> TypeM lore a #

(<*>) :: TypeM lore (a -> b) -> TypeM lore a -> TypeM lore b #

liftA2 :: (a -> b -> c) -> TypeM lore a -> TypeM lore b -> TypeM lore c #

(*>) :: TypeM lore a -> TypeM lore b -> TypeM lore b #

(<*) :: TypeM lore a -> TypeM lore b -> TypeM lore a #

Checkable lore => HasScope (Aliases lore) (TypeM lore) Source # 
Instance details

Defined in Futhark.TypeCheck

Methods

lookupType :: VName -> TypeM lore Type Source #

lookupInfo :: VName -> TypeM lore (NameInfo (Aliases lore)) Source #

askScope :: TypeM lore (Scope (Aliases lore)) Source #

asksScope :: (Scope (Aliases lore) -> a) -> TypeM lore a Source #

bad :: ErrorCase lore -> TypeM lore a Source #

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), CheckableOp lore) => Checkable lore where Source #

The class of lores that can be type-checked.

Minimal complete definition

Nothing

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 #

matchPattern :: Pattern (Aliases lore) -> Exp (Aliases lore) -> TypeM lore () Source #

primFParam :: VName -> PrimType -> TypeM lore (FParam (Aliases lore)) Source #

matchReturnType :: [RetType lore] -> Result -> TypeM lore () Source #

matchBranchType :: [BranchType lore] -> Body (Aliases lore) -> TypeM lore () Source #

checkExpLore :: ExpAttr lore ~ () => ExpAttr lore -> TypeM lore () Source #

checkBodyLore :: BodyAttr lore ~ () => BodyAttr lore -> TypeM lore () Source #

checkFParamLore :: FParamAttr lore ~ DeclType => VName -> FParamAttr lore -> TypeM lore () Source #

checkLParamLore :: LParamAttr lore ~ Type => VName -> LParamAttr lore -> TypeM lore () Source #

checkLetBoundLore :: LetAttr lore ~ Type => VName -> LetAttr lore -> TypeM lore () Source #

checkRetType :: RetType lore ~ DeclExtType => [RetType lore] -> TypeM lore () Source #

matchPattern :: Pattern (Aliases lore) -> Exp (Aliases lore) -> TypeM lore () Source #

primFParam :: FParamAttr lore ~ DeclType => VName -> PrimType -> TypeM lore (FParam (Aliases lore)) Source #

matchReturnType :: RetType lore ~ DeclExtType => [RetType lore] -> Result -> TypeM lore () Source #

matchBranchType :: BranchType lore ~ ExtType => [BranchType lore] -> Body (Aliases lore) -> TypeM lore () Source #

Instances
Checkable SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

Checkable InKernel Source # 
Instance details

Defined in Futhark.Representation.Kernels

Checkable Kernels Source # 
Instance details

Defined in Futhark.Representation.Kernels

Checkable InKernel Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Checkable ExplicitMemory Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

type Occurences = [Occurence] Source #

type UsageMap = Map VName [Usage] 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.

checkExp :: Checkable lore => Exp (Aliases lore) -> TypeM lore () Source #

checkStms :: Checkable lore => Stms (Aliases lore) -> TypeM lore a -> TypeM lore a Source #

checkStm :: Checkable lore => Stm (Aliases lore) -> TypeM lore a -> TypeM lore a Source #

checkType :: Checkable lore => TypeBase Shape u -> TypeM lore () Source #

matchExtPattern :: Checkable lore => Pattern (Aliases lore) -> [ExtType] -> TypeM lore () Source #

matchExtBranchType :: Checkable lore => [ExtType] -> Body (Aliases lore) -> TypeM lore () Source #

argType :: Arg -> Type Source #

argAliases :: Arg -> Names Source #

Remove all aliases from the Arg.

noArgAliases :: Arg -> Arg Source #

checkArg :: Checkable lore => SubExp -> TypeM lore Arg Source #

checkSOACArrayArgs :: Checkable lore => SubExp -> [VName] -> TypeM lore [Arg] Source #

checkLambda :: Checkable lore => Lambda (Aliases lore) -> [Arg] -> TypeM lore () Source #

checkFun' :: Checkable lore => (Name, [DeclExtType], [(VName, NameInfo (Aliases lore))], BodyT (Aliases lore)) -> [(VName, Names)] -> TypeM lore () -> TypeM lore () Source #

checkLambdaParams :: Checkable lore => [LParam lore] -> TypeM lore () Source #

checkBody :: Checkable lore => Body (Aliases lore) -> TypeM lore () Source #

checkLambdaBody :: Checkable lore => [Type] -> Body (Aliases lore) -> TypeM lore () Source #

consume :: Checkable lore => Names -> TypeM lore () Source #

Proclaim that we have written to the given variables.

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.

binding :: Checkable lore => Scope (Aliases lore) -> TypeM lore a -> TypeM lore a Source #