futhark-0.15.5: An optimising compiler for a functional, array-oriented language.
Safe HaskellNone
LanguageHaskell2010

Futhark.TypeCheck

Description

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

Synopsis

Interface

checkProg :: Checkable lore => Prog (Aliases 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

Instances details
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 #

data ErrorCase lore Source #

Information about an error during type checking. The Show instance for this type produces a human-readable description.

Instances

Instances details
Checkable lore => Show (ErrorCase lore) Source # 
Instance details

Defined in Futhark.TypeCheck

Methods

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

show :: ErrorCase lore -> String #

showList :: [ErrorCase lore] -> ShowS #

Extensionality

data TypeM lore a Source #

The type checker runs in this monad.

Instances

Instances details
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 #

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.

message :: Pretty a => String -> a -> String Source #

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 #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Instances

Instances details
Checkable SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

Checkable Kernels Source # 
Instance details

Defined in Futhark.Representation.Kernels

Checkable ExplicitMemory Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

class Attributes lore => CheckableOp lore where Source #

Methods

checkOp :: OpWithAliases (Op lore) -> TypeM lore () Source #

Used at top level; can be locally changed with checkOpWith.

type Occurences = [Occurence] Source #

checkOpWith :: (OpWithAliases (Op lore) -> TypeM lore ()) -> TypeM lore 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 #

checkBody :: Checkable lore => Body (Aliases lore) -> TypeM lore [Names] 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 #