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

Safe HaskellNone
LanguageHaskell2010

Futhark.Representation.AST.Attributes

Contents

Description

This module provides various simple ways to query and manipulate fundamental Futhark terms, such as types and values. The intent is to keep Futhark.Reprsentation.AST.Syntax simple, and put whatever embellishments we need here. This is an internal, desugared representation.

Synopsis

Documentation

Built-in functions

isBuiltInFunction :: Name -> Bool Source #

isBuiltInFunction k is True if k is an element of builtInFunctions.

builtInFunctions :: Map Name (PrimType, [PrimType]) Source #

A map of all built-in functions and their types.

Extra tools

funDefByName :: Name -> Prog lore -> Maybe (FunDef lore) Source #

Find the function of the given name in the Futhark program.

asBasicOp :: Exp lore -> Maybe (BasicOp lore) Source #

If the expression is a BasicOp, return that BasicOp, otherwise Nothing.

safeExp :: IsOp (Op lore) => Exp lore -> Bool Source #

An expression is safe if it is always well-defined (assuming that any required certificates have been checked) in any context. For example, array indexing is not safe, as the index may be out of bounds. On the other hand, adding two numbers cannot fail.

subExpVars :: [SubExp] -> [VName] Source #

Return the variable names used in Var subexpressions. May contain duplicates.

subExpVar :: SubExp -> Maybe VName Source #

If the BasicOp is a Var return the variable name.

shapeVars :: Shape -> [VName] Source #

Return the variable dimension sizes. May contain duplicates.

commutativeLambda :: Lambda lore -> Bool Source #

Does the given lambda represent a known commutative function? Based on pattern matching and checking whether the lambda represents a known arithmetic operator; don't expect anything clever here.

entryPointSize :: EntryPointType -> Int Source #

How many value parameters are accepted by this entry point? This is used to determine which of the function parameters correspond to the parameters of the original function (they must all come at the end).

defAux :: attr -> StmAux attr Source #

A StmAux with empty Certificates.

stmCerts :: Stm lore -> Certificates Source #

The certificates associated with a statement.

certify :: Certificates -> Stm lore -> Stm lore Source #

Add certificates to a statement.

expExtTypesFromPattern :: Typed attr => PatternT attr -> [ExtType] Source #

Construct the type of an expression that would match the pattern.

patternFromParams :: [Param attr] -> PatternT attr Source #

Create a pattern corresponding to some parameters.

class (Eq op, Ord op, Show op, TypedOp op, Rename op, Substitute op, FreeIn op, Pretty op) => IsOp op where Source #

A type class for operations.

Methods

safeOp :: op -> Bool Source #

Like safeExp, but for arbitrary ops.

cheapOp :: op -> Bool Source #

Should we try to hoist this out of branches?

Instances
IsOp () Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes

Methods

safeOp :: () -> Bool Source #

cheapOp :: () -> Bool Source #

Attributes lore => IsOp (SOAC lore) Source # 
Instance details

Defined in Futhark.Representation.SOACS.SOAC

Methods

safeOp :: SOAC lore -> Bool Source #

cheapOp :: SOAC lore -> Bool Source #

Attributes lore => IsOp (KernelExp lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

Methods

safeOp :: KernelExp lore -> Bool Source #

cheapOp :: KernelExp lore -> Bool Source #

Attributes lore => IsOp (Kernel lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Methods

safeOp :: Kernel lore -> Bool Source #

cheapOp :: Kernel lore -> Bool Source #

IsOp inner => IsOp (MemOp inner) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Methods

safeOp :: MemOp inner -> Bool Source #

cheapOp :: MemOp inner -> Bool Source #

class (Annotations lore, PrettyLore lore, Renameable lore, Substitutable lore, FreeAttr (ExpAttr lore), FreeIn (LetAttr lore), FreeAttr (BodyAttr lore), FreeIn (FParamAttr lore), FreeIn (LParamAttr lore), FreeIn (RetType lore), FreeIn (BranchType lore), IsOp (Op lore)) => Attributes lore where Source #

Lore-specific attributes; also means the lore supports some basic facilities.

Methods

expTypesFromPattern :: (HasScope lore m, Monad m) => Pattern lore -> m [BranchType lore] Source #

Given a pattern, construct the type of a body that would match it. An implementation for many lores would be expExtTypesFromPattern.

Instances
Attributes SOACS Source # 
Instance details

Defined in Futhark.Representation.SOACS

Attributes InKernel Source # 
Instance details

Defined in Futhark.Representation.Kernels

Attributes Kernels Source # 
Instance details

Defined in Futhark.Representation.Kernels

Attributes InKernel Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Attributes ExplicitMemory Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

(Attributes lore, CanBeRanged (Op lore)) => Attributes (Ranges lore) Source # 
Instance details

Defined in Futhark.Representation.Ranges

Methods

expTypesFromPattern :: (HasScope (Ranges lore) m, Monad m) => Pattern (Ranges lore) -> m [BranchType (Ranges lore)] Source #

(Attributes lore, CanBeAliased (Op lore)) => Attributes (Aliases lore) Source # 
Instance details

Defined in Futhark.Representation.Aliases

Methods

expTypesFromPattern :: (HasScope (Aliases lore) m, Monad m) => Pattern (Aliases lore) -> m [BranchType (Aliases lore)] Source #

(Attributes lore, CanBeWise (Op lore)) => Attributes (Wise lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

Methods

expTypesFromPattern :: (HasScope (Wise lore) m, Monad m) => Pattern (Wise lore) -> m [BranchType (Wise lore)] Source #