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

Safe HaskellNone
LanguageHaskell2010

Futhark.Representation.AST.Attributes.Names

Contents

Description

Facilities for determining which names are used in some syntactic construct. The most important interface is the FreeIn class and its instances, but for reasons related to the Haskell type system, some constructs have specialised functions.

Synopsis

Class

class FreeIn a where Source #

A class indicating that we can obtain free variable information from values of this type.

Methods

freeIn :: a -> Names Source #

Instances
FreeIn Bool Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: Bool -> Names Source #

FreeIn Int Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: Int -> Names Source #

FreeIn () Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: () -> Names Source #

FreeIn VName Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: VName -> Names Source #

FreeIn Names Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: Names -> Names Source #

FreeIn SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: SubExp -> Names Source #

FreeIn Certificates Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

FreeIn Ident Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: Ident -> Names Source #

FreeIn ScalExp Source # 
Instance details

Defined in Futhark.Analysis.ScalExp

Methods

freeIn :: ScalExp -> Names Source #

FreeIn KnownBound Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

FreeIn Names' Source # 
Instance details

Defined in Futhark.Representation.Aliases

Methods

freeIn :: Names' -> Names Source #

FreeIn ExpWisdom Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

FreeIn VarWisdom Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

FreeIn SplitOrdering Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

FreeIn WhichThreads Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

FreeIn KernelResult Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

FreeIn LoopNesting Source # 
Instance details

Defined in Futhark.Pass.ExtractKernels.Distribution

FreeIn MemReturn Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

FreeIn MemBind Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Methods

freeIn :: MemBind -> Names Source #

FreeIn Arg Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn :: Arg -> Names Source #

FreeIn ExpLeaf Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn :: ExpLeaf -> Names Source #

FreeIn Size Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn :: Size -> Names Source #

FreeIn Sequential Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Sequential

FreeIn AtomicOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

FreeIn KernelOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

FreeIn Kernel Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

Methods

freeIn :: Kernel -> Names Source #

FreeIn HostOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

Methods

freeIn :: HostOp -> Names Source #

FreeIn a => FreeIn [a] Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: [a] -> Names Source #

FreeIn a => FreeIn (Maybe a) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: Maybe a -> Names Source #

FreeIn attr => FreeIn (PatElemT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: PatElemT attr -> Names Source #

FreeIn d => FreeIn (DimIndex d) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: DimIndex d -> Names Source #

FreeIn attr => FreeIn (ParamT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: ParamT attr -> Names Source #

FreeIn d => FreeIn (Ext d) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: Ext d -> Names Source #

FreeIn d => FreeIn (ShapeBase d) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: ShapeBase d -> Names Source #

FreeIn a => FreeIn (IfAttr a) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: IfAttr a -> Names Source #

FreeIn (LParamAttr lore) => FreeIn (LoopForm lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: LoopForm lore -> Names Source #

FreeIn d => FreeIn (DimChange d) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: DimChange d -> Names Source #

FreeIn (Stm lore) => FreeIn (Stms lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: Stms lore -> Names Source #

FreeIn attr => FreeIn (StmAux attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: StmAux attr -> Names Source #

FreeIn attr => FreeIn (PatternT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: PatternT attr -> Names Source #

FreeIn v => FreeIn (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

freeIn :: PrimExp v -> Names Source #

FreeIn num => FreeIn (IxFun num) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory.Lmad

Methods

freeIn :: IxFun num -> Names Source #

FreeIn num => FreeIn (IxFun num) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory.IndexFunction

Methods

freeIn :: IxFun num -> Names Source #

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

Defined in Futhark.Representation.SOACS.SOAC

Methods

freeIn :: SOAC lore -> Names Source #

Attributes lore => FreeIn (GroupStreamLambda lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.KernelExp

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

Defined in Futhark.Representation.Kernels.KernelExp

Methods

freeIn :: KernelExp lore -> Names Source #

Attributes lore => FreeIn (KernelBody lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Methods

freeIn :: KernelBody lore -> Names Source #

(Attributes lore, FreeIn (LParamAttr lore)) => FreeIn (Kernel lore) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Methods

freeIn :: Kernel lore -> Names Source #

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

Defined in Futhark.Representation.ExplicitMemory

Methods

freeIn :: MemOp inner -> Names Source #

FreeIn (Count u) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn :: Count u -> Names Source #

FreeIn a => FreeIn (Code a) Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn :: Code a -> Names Source #

(FreeIn a, FreeIn b) => FreeIn (a, b) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: (a, b) -> Names Source #

FreeIn shape => FreeIn (TypeBase shape u) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: TypeBase shape u -> Names Source #

(FreeIn a, FreeIn b, FreeIn c) => FreeIn (a, b, c) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: (a, b, c) -> Names Source #

(FreeIn d, FreeIn ret) => FreeIn (MemInfo d u ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Methods

freeIn :: MemInfo d u ret -> Names Source #

type Names = Set VName Source #

A set of names.

Specialised Functions

freeInStmsAndRes :: (FreeIn (Op lore), FreeIn (LetAttr lore), FreeIn (LParamAttr lore), FreeIn (FParamAttr lore), FreeAttr (BodyAttr lore), FreeAttr (ExpAttr lore)) => Stms lore -> Result -> Names Source #

Return the set of variable names that are free in the given statements and result. Filters away the names that are bound by the statements.

freeInBody :: (FreeAttr (ExpAttr lore), FreeAttr (BodyAttr lore), FreeIn (FParamAttr lore), FreeIn (LParamAttr lore), FreeIn (LetAttr lore), FreeIn (Op lore)) => Body lore -> Names Source #

Return the set of variable names that are free in the given body.

freeInExp :: (FreeAttr (ExpAttr lore), FreeAttr (BodyAttr lore), FreeIn (FParamAttr lore), FreeIn (LParamAttr lore), FreeIn (LetAttr lore), FreeIn (Op lore)) => Exp lore -> Names Source #

Return the set of variable names that are free in the given expression.

freeInStm :: (FreeAttr (ExpAttr lore), FreeAttr (BodyAttr lore), FreeIn (FParamAttr lore), FreeIn (LParamAttr lore), FreeIn (LetAttr lore), FreeIn (Op lore)) => Stm lore -> Names Source #

Return the set of variable names that are free in the given binding.

freeInLambda :: (FreeAttr (ExpAttr lore), FreeAttr (BodyAttr lore), FreeIn (FParamAttr lore), FreeIn (LParamAttr lore), FreeIn (LetAttr lore), FreeIn (Op lore)) => Lambda lore -> Names Source #

Return the set of variable names that are free in the given lambda, including shape annotations in the parameters.

Bound Names

boundInBody :: Body lore -> Names Source #

The names bound by the bindings immediately in a BodyT.

boundByStm :: Stm lore -> Names Source #

The names bound by a binding.

boundByStms :: Stms lore -> Names Source #

The names bound by the bindings.

boundByLambda :: Lambda lore -> [VName] Source #

The names of the lambda parameters plus the index parameter.

class FreeIn attr => FreeAttr attr where Source #

Either return precomputed free names stored in the attribute, or the freshly computed names. Relies on lazy evaluation to avoid the work.

Minimal complete definition

Nothing

Methods

precomputed :: attr -> Names -> Names Source #

Instances
FreeAttr () Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

precomputed :: () -> Names -> Names Source #

FreeAttr KnownBound Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

FreeAttr Names' Source # 
Instance details

Defined in Futhark.Representation.Aliases

FreeAttr ExpWisdom Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

FreeAttr a => FreeAttr [a] Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

precomputed :: [a] -> Names -> Names Source #

FreeAttr a => FreeAttr (Maybe a) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

precomputed :: Maybe a -> Names -> Names Source #

(FreeAttr a, FreeIn b) => FreeAttr (a, b) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

precomputed :: (a, b) -> Names -> Names Source #