Safe Haskell | None |
---|---|
Language | GHC2021 |
Futhark.IR.Rep
Description
The core Futhark AST is parameterised by a rep
type parameter,
which is then used to invoke the type families defined here.
Synopsis
- class (Show (LetDec l), Show (ExpDec l), Show (BodyDec l), Show (FParamInfo l), Show (LParamInfo l), Show (RetType l), Show (BranchType l), Show (Op l), Eq (LetDec l), Eq (ExpDec l), Eq (BodyDec l), Eq (FParamInfo l), Eq (LParamInfo l), Eq (RetType l), Eq (BranchType l), Eq (Op l), Ord (LetDec l), Ord (ExpDec l), Ord (BodyDec l), Ord (FParamInfo l), Ord (LParamInfo l), Ord (RetType l), Ord (BranchType l), Ord (Op l), IsRetType (RetType l), IsBodyType (BranchType l), Typed (FParamInfo l), Typed (LParamInfo l), Typed (LetDec l), DeclTyped (FParamInfo l)) => RepTypes l where
- type LetDec l
- type ExpDec l
- type BodyDec l
- type FParamInfo l
- type LParamInfo l
- type RetType l
- type BranchType l
- type OpC l :: Type -> Type
- type Op l = OpC l l
- data NoOp (rep :: k) = NoOp
- module Futhark.IR.RetType
Documentation
class (Show (LetDec l), Show (ExpDec l), Show (BodyDec l), Show (FParamInfo l), Show (LParamInfo l), Show (RetType l), Show (BranchType l), Show (Op l), Eq (LetDec l), Eq (ExpDec l), Eq (BodyDec l), Eq (FParamInfo l), Eq (LParamInfo l), Eq (RetType l), Eq (BranchType l), Eq (Op l), Ord (LetDec l), Ord (ExpDec l), Ord (BodyDec l), Ord (FParamInfo l), Ord (LParamInfo l), Ord (RetType l), Ord (BranchType l), Ord (Op l), IsRetType (RetType l), IsBodyType (BranchType l), Typed (FParamInfo l), Typed (LParamInfo l), Typed (LetDec l), DeclTyped (FParamInfo l)) => RepTypes l Source #
A collection of type families giving various common types for a representation, along with constraints specifying that the types they map to should satisfy some minimal requirements.
Associated Types
Decoration for every let-pattern element.
Decoration for every expression.
type ExpDec l = ()
Decoration for every body.
type BodyDec l = ()
type FParamInfo l Source #
Decoration for every (non-lambda) function parameter.
type FParamInfo l = DeclType
type LParamInfo l Source #
Decoration for every lambda function parameter.
type LParamInfo l = Type
The return type decoration of function calls.
type RetType l = DeclExtType
type BranchType l Source #
The return type decoration of branches.
type BranchType l = ExtType
type OpC l :: Type -> Type Source #
Type constructor for the extensible operation. The somewhat
funky definition is to ensure that we can change the "inner"
representation in a generic way (e.g. add aliasing information)
In most code, you will use the Op
alias instead.
Instances
Returns nothing and does nothing. Placeholder for when we don't really want an operation.
Constructors
NoOp |
Instances
CanBeAliased (NoOp :: Type -> Type) Source # | |
Defined in Futhark.IR.Aliases Methods addOpAliases :: AliasableRep rep => AliasTable -> NoOp rep -> NoOp (Aliases rep) Source # | |
OpReturns (HostOp (NoOp :: Type -> Type)) Source # | |
OpReturns (MCOp (NoOp :: Type -> Type)) Source # | |
OpReturns (NoOp :: Type -> Type) Source # | |
IsOp (NoOp :: Type -> Type) Source # | |
AliasedOp (NoOp :: Type -> Type) Source # | |
TypedOp (NoOp :: Type -> Type) Source # | |
RephraseOp (NoOp :: Type -> Type) Source # | |
Defined in Futhark.IR.Rephrase | |
CanBeWise (NoOp :: Type -> Type) Source # | |
Defined in Futhark.Optimise.Simplify.Rep | |
Show (NoOp rep) Source # | |
OpMetrics (NoOp rep) Source # | |
IndexOp (NoOp rep) Source # | |
FreeIn (NoOp rep) Source # | |
TopDownHelper (HostOp (NoOp :: Type -> Type) (Aliases GPUMem)) Source # | |
TopDownHelper (NoOp rep) Source # | |
Defined in Futhark.Optimise.ArrayShortCircuiting.TopdownAnalysis Methods innerNonNegatives :: [VName] -> NoOp rep -> Names innerKnownLessThan :: NoOp rep -> [(VName, PrimExp VName)] scopeHelper :: NoOp rep -> Scope rep0 | |
CSEInOp (NoOp rep) Source # | |
Defined in Futhark.Optimise.CSE | |
SizeSubst (NoOp rep) Source # | |
Rename (NoOp rep) Source # | |
Substitute (NoOp rep) Source # | |
Defined in Futhark.Transform.Substitute | |
Eq (NoOp rep) Source # | |
Ord (NoOp rep) Source # | |
Defined in Futhark.IR.Rep | |
Pretty (NoOp rep) Source # | |
Defined in Futhark.IR.Pretty |
module Futhark.IR.RetType