Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- module Futhark.Representation.AST.Attributes.Reshape
- module Futhark.Representation.AST.Attributes.Rearrange
- module Futhark.Representation.AST.Attributes.Types
- module Futhark.Representation.AST.Attributes.Constants
- module Futhark.Representation.AST.Attributes.TypeOf
- module Futhark.Representation.AST.Attributes.Patterns
- module Futhark.Representation.AST.Attributes.Names
- module Futhark.Representation.AST.RetType
- isBuiltInFunction :: Name -> Bool
- builtInFunctions :: Map Name (PrimType, [PrimType])
- funDefByName :: Name -> Prog lore -> Maybe (FunDef lore)
- asBasicOp :: Exp lore -> Maybe (BasicOp lore)
- safeExp :: IsOp (Op lore) => Exp lore -> Bool
- subExpVars :: [SubExp] -> [VName]
- subExpVar :: SubExp -> Maybe VName
- shapeVars :: Shape -> [VName]
- commutativeLambda :: Lambda lore -> Bool
- entryPointSize :: EntryPointType -> Int
- defAux :: attr -> StmAux attr
- stmCerts :: Stm lore -> Certificates
- certify :: Certificates -> Stm lore -> Stm lore
- expExtTypesFromPattern :: Typed attr => PatternT attr -> [ExtType]
- patternFromParams :: [Param attr] -> PatternT attr
- class (Eq op, Ord op, Show op, TypedOp op, Rename op, Substitute op, FreeIn op, Pretty op) => IsOp op where
- 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
- expTypesFromPattern :: (HasScope lore m, Monad m) => Pattern lore -> m [BranchType lore]
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.
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.
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).
stmCerts :: Stm lore -> Certificates Source #
The certificates associated with 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.
Like safeExp
, but for arbitrary ops.
cheapOp :: op -> Bool Source #
Should we try to hoist this out of branches?
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.
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
.