futhark-0.25.15: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe-Inferred
LanguageGHC2021

Futhark.IR.Prop

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.IR.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

asBasicOp :: Exp rep -> Maybe BasicOp Source #

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

safeExp :: ASTRep rep => Exp rep -> 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 SubExp is a Var return the variable name.

commutativeLambda :: Lambda rep -> 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.

defAux :: dec -> StmAux dec Source #

A StmAux with empty Certs.

stmCerts :: Stm rep -> Certs Source #

The certificates associated with a statement.

certify :: Certs -> Stm rep -> Stm rep Source #

Add certificates to a statement.

expExtTypesFromPat :: Typed dec => Pat dec -> [ExtType] Source #

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

attrsForAssert :: Attrs -> Attrs Source #

Keep only those attributes that are relevant for Assert expressions.

lamIsBinOp :: ASTRep rep => Lambda rep -> Maybe [(BinOp, PrimType, VName, VName)] Source #

Horizontally fission a lambda that models a binary operator.

type ASTConstraints a = (Eq a, Ord a, Show a, Rename a, Substitute a, FreeIn a, Pretty a) Source #

A handy shorthand for properties that we usually want for things we stuff into ASTs.

class TypedOp op => IsOp op where Source #

A type class for operations.

Methods

safeOp :: ASTRep rep => op rep -> Bool Source #

Like safeExp, but for arbitrary ops.

cheapOp :: ASTRep rep => op rep -> Bool Source #

Should we try to hoist this out of branches?

opDependencies :: ASTRep rep => op rep -> [Names] Source #

Compute the data dependencies of an operation.

Instances

Instances details
IsOp SOAC Source # 
Instance details

Defined in Futhark.IR.SOACS.SOAC

Methods

safeOp :: ASTRep rep => SOAC rep -> Bool Source #

cheapOp :: ASTRep rep => SOAC rep -> Bool Source #

opDependencies :: ASTRep rep => SOAC rep -> [Names] Source #

IsOp op => IsOp (HostOp op) Source # 
Instance details

Defined in Futhark.IR.GPU.Op

Methods

safeOp :: ASTRep rep => HostOp op rep -> Bool Source #

cheapOp :: ASTRep rep => HostOp op rep -> Bool Source #

opDependencies :: ASTRep rep => HostOp op rep -> [Names] Source #

IsOp op => IsOp (MCOp op) Source # 
Instance details

Defined in Futhark.IR.MC.Op

Methods

safeOp :: ASTRep rep => MCOp op rep -> Bool Source #

cheapOp :: ASTRep rep => MCOp op rep -> Bool Source #

opDependencies :: ASTRep rep => MCOp op rep -> [Names] Source #

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

Defined in Futhark.IR.Mem

Methods

safeOp :: ASTRep rep => MemOp inner rep -> Bool Source #

cheapOp :: ASTRep rep => MemOp inner rep -> Bool Source #

opDependencies :: ASTRep rep => MemOp inner rep -> [Names] Source #

IsOp (NoOp :: Type -> Type) Source # 
Instance details

Defined in Futhark.IR.Prop

Methods

safeOp :: ASTRep rep => NoOp rep -> Bool Source #

cheapOp :: ASTRep rep => NoOp rep -> Bool Source #

opDependencies :: ASTRep rep => NoOp rep -> [Names] Source #

ASTConstraints lvl => IsOp (SegOp lvl) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

safeOp :: ASTRep rep => SegOp lvl rep -> Bool Source #

cheapOp :: ASTRep rep => SegOp lvl rep -> Bool Source #

opDependencies :: ASTRep rep => SegOp lvl rep -> [Names] Source #

class (RepTypes rep, PrettyRep rep, Renameable rep, Substitutable rep, FreeDec (ExpDec rep), FreeIn (LetDec rep), FreeDec (BodyDec rep), FreeIn (FParamInfo rep), FreeIn (LParamInfo rep), FreeIn (RetType rep), FreeIn (BranchType rep), ASTConstraints (OpC rep rep), IsOp (OpC rep), RephraseOp (OpC rep)) => ASTRep rep where Source #

Representation-specific attributes; also means the rep supports some basic facilities.

Methods

expTypesFromPat :: (HasScope rep m, Monad m) => Pat (LetDec rep) -> m [BranchType rep] Source #

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

Instances

Instances details
ASTRep GPU Source # 
Instance details

Defined in Futhark.IR.GPU

ASTRep GPUMem Source # 
Instance details

Defined in Futhark.IR.GPUMem

ASTRep MC Source # 
Instance details

Defined in Futhark.IR.MC

ASTRep MCMem Source # 
Instance details

Defined in Futhark.IR.MCMem

ASTRep SOACS Source # 
Instance details

Defined in Futhark.IR.SOACS

ASTRep Seq Source # 
Instance details

Defined in Futhark.IR.Seq

ASTRep SeqMem Source # 
Instance details

Defined in Futhark.IR.SeqMem

(ASTRep rep, AliasedOp (OpC rep), ASTConstraints (OpC rep (Aliases rep))) => ASTRep (Aliases rep) Source # 
Instance details

Defined in Futhark.IR.Aliases

Methods

expTypesFromPat :: (HasScope (Aliases rep) m, Monad m) => Pat (LetDec (Aliases rep)) -> m [BranchType (Aliases rep)] Source #

(Informing rep, IsOp (OpC rep)) => ASTRep (Wise rep) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Rep

Methods

expTypesFromPat :: (HasScope (Wise rep) m, Monad m) => Pat (LetDec (Wise rep)) -> m [BranchType (Wise rep)] Source #