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

Futhark.IR.Prop.Names

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

Free names

data Names Source #

A set of names.

Instances

Instances details
Eq Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

(==) :: Names -> Names -> Bool #

(/=) :: Names -> Names -> Bool #

Show Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

showsPrec :: Int -> Names -> ShowS #

show :: Names -> String #

showList :: [Names] -> ShowS #

Semigroup Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

(<>) :: Names -> Names -> Names #

sconcat :: NonEmpty Names -> Names #

stimes :: Integral b => b -> Names -> Names #

Monoid Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

mempty :: Names #

mappend :: Names -> Names -> Names #

mconcat :: [Names] -> Names #

Pretty Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

ppr :: Names -> Doc #

pprPrec :: Int -> Names -> Doc #

pprList :: [Names] -> Doc #

FreeIn Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Names -> FV Source #

Substitute Names Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename Names Source # 
Instance details

Defined in Futhark.Transform.Rename

AliasesOf Names Source # 
Instance details

Defined in Futhark.IR.Prop.Aliases

MonadState Names (TypeM lore) Source # 
Instance details

Defined in Futhark.TypeCheck

Methods

get :: TypeM lore Names #

put :: Names -> TypeM lore () #

state :: (Names -> (a, Names)) -> TypeM lore a #

nameIn :: VName -> Names -> Bool Source #

Does the set of names contain this name?

oneName :: VName -> Names Source #

Construct a name set from a single name.

namesFromList :: [VName] -> Names Source #

Construct a name set from a list. Slow.

namesToList :: Names -> [VName] Source #

Turn a name set into a list of names. Slow.

namesIntersection :: Names -> Names -> Names Source #

The intersection of two name sets.

namesIntersect :: Names -> Names -> Bool Source #

Do the two name sets intersect?

namesSubtract :: Names -> Names -> Names Source #

Subtract the latter name set from the former.

mapNames :: (VName -> VName) -> Names -> Names Source #

Map over the names in a set.

Class

class FreeIn a where Source #

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

Minimal complete definition

Nothing

Methods

freeIn' :: a -> FV Source #

Instances

Instances details
FreeIn Bool Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Bool -> FV Source #

FreeIn Int Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Int -> FV Source #

FreeIn () Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: () -> FV Source #

FreeIn VName Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: VName -> FV Source #

FreeIn SubExp Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: SubExp -> FV Source #

FreeIn Certificates Source # 
Instance details

Defined in Futhark.IR.Prop.Names

FreeIn Ident Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Ident -> FV Source #

FreeIn Space Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Space -> FV Source #

FreeIn Attrs Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Attrs -> FV Source #

FreeIn FV Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: FV -> FV Source #

FreeIn Names Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Names -> FV Source #

FreeIn ScalExp Source # 
Instance details

Defined in Futhark.Analysis.ScalExp

Methods

freeIn' :: ScalExp -> FV Source #

FreeIn KnownBound Source # 
Instance details

Defined in Futhark.IR.Prop.Ranges

FreeIn Names' Source # 
Instance details

Defined in Futhark.IR.Aliases

Methods

freeIn' :: Names' -> FV Source #

FreeIn ExpWisdom Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

Methods

freeIn' :: ExpWisdom -> FV Source #

FreeIn VarWisdom Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

Methods

freeIn' :: VarWisdom -> FV Source #

FreeIn Indexed Source # 
Instance details

Defined in Futhark.Analysis.SymbolTable

Methods

freeIn' :: Indexed -> FV Source #

FreeIn MemReturn Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

freeIn' :: MemReturn -> FV Source #

FreeIn MemBind Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

freeIn' :: MemBind -> FV Source #

FreeIn KernelResult Source # 
Instance details

Defined in Futhark.IR.SegOp

FreeIn SplitOrdering Source # 
Instance details

Defined in Futhark.IR.SegOp

FreeIn LoopNesting Source # 
Instance details

Defined in Futhark.Pass.ExtractKernels.Distribution

FreeIn SizeOp Source # 
Instance details

Defined in Futhark.IR.Kernels.Kernel

Methods

freeIn' :: SizeOp -> FV Source #

FreeIn SegLevel Source # 
Instance details

Defined in Futhark.IR.Kernels.Kernel

Methods

freeIn' :: SegLevel -> FV Source #

FreeIn Arg Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: Arg -> FV Source #

FreeIn ExpLeaf Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: ExpLeaf -> FV Source #

FreeIn Sequential Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Sequential

FreeIn AtomicOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

Methods

freeIn' :: AtomicOp -> FV Source #

FreeIn KernelOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

Methods

freeIn' :: KernelOp -> FV Source #

FreeIn Kernel Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

Methods

freeIn' :: Kernel -> FV Source #

FreeIn HostOp Source # 
Instance details

Defined in Futhark.CodeGen.ImpCode.Kernels

Methods

freeIn' :: HostOp -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: [a] -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Maybe a -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: PatElemT dec -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: DimIndex d -> FV Source #

FreeIn dec => FreeIn (Param dec) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Param dec -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Ext d -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: ShapeBase d -> FV Source #

(FreeDec (ExpDec lore), FreeDec (BodyDec lore), FreeIn (FParamInfo lore), FreeIn (LParamInfo lore), FreeIn (LetDec lore), FreeIn (RetType lore), FreeIn (Op lore)) => FreeIn (FunDef lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: FunDef lore -> FV Source #

(FreeDec (ExpDec lore), FreeDec (BodyDec lore), FreeIn (FParamInfo lore), FreeIn (LParamInfo lore), FreeIn (LetDec lore), FreeIn (Op lore)) => FreeIn (Lambda lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Lambda lore -> FV Source #

(FreeDec (ExpDec lore), FreeDec (BodyDec lore), FreeIn (FParamInfo lore), FreeIn (LParamInfo lore), FreeIn (LetDec lore), FreeIn (Op lore)) => FreeIn (Exp lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Exp lore -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: IfDec a -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: LoopForm lore -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: DimChange d -> FV Source #

(FreeDec (ExpDec lore), FreeDec (BodyDec lore), FreeIn (FParamInfo lore), FreeIn (LParamInfo lore), FreeIn (LetDec lore), FreeIn (Op lore)) => FreeIn (Body lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Body lore -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Stms lore -> FV Source #

(FreeDec (ExpDec lore), FreeDec (BodyDec lore), FreeIn (FParamInfo lore), FreeIn (LParamInfo lore), FreeIn (LetDec lore), FreeIn (Op lore)) => FreeIn (Stm lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Stm lore -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: StmAux dec -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: PatternT dec -> FV Source #

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

Defined in Futhark.Analysis.PrimExp

Methods

freeIn' :: PrimExp v -> FV Source #

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

Defined in Futhark.IR.Mem.IxFun

Methods

freeIn' :: IxFun num -> FV Source #

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

Defined in Futhark.IR.SOACS.SOAC

Methods

freeIn' :: SOAC lore -> FV Source #

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

Defined in Futhark.IR.Mem

Methods

freeIn' :: MemOp inner -> FV Source #

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

Defined in Futhark.IR.SegOp

Methods

freeIn' :: KernelBody lore -> FV Source #

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

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: Code a -> FV Source #

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

Defined in Futhark.CodeGen.ImpCode

Methods

freeIn' :: Functions a -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: (a, b) -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: TypeBase shape u -> FV Source #

FreeIn e => FreeIn (Count u e) Source # 
Instance details

Defined in Futhark.IR.Kernels.Sizes

Methods

freeIn' :: Count u e -> FV Source #

(ASTLore lore, FreeIn (LParamInfo lore), FreeIn lvl) => FreeIn (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.IR.SegOp

Methods

freeIn' :: SegOp lvl lore -> FV Source #

(ASTLore lore, FreeIn op) => FreeIn (HostOp lore op) Source # 
Instance details

Defined in Futhark.IR.Kernels.Kernel

Methods

freeIn' :: HostOp lore op -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

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

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

Defined in Futhark.IR.Mem

Methods

freeIn' :: MemInfo d u ret -> FV Source #

freeIn :: FreeIn a => a -> Names Source #

The free variables of some syntactic construct.

Specialised Functions

freeInStmsAndRes :: (FreeIn (Op lore), FreeIn (LetDec lore), FreeIn (LParamInfo lore), FreeIn (FParamInfo lore), FreeDec (BodyDec lore), FreeDec (ExpDec lore)) => Stms lore -> Result -> FV 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.

Bound Names

boundInBody :: Body lore -> Names Source #

The names bound by the bindings immediately in a Body.

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.

Efficient computation

class FreeIn dec => FreeDec dec 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 :: dec -> FV -> FV Source #

Instances

Instances details
FreeDec () Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

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

FreeDec KnownBound Source # 
Instance details

Defined in Futhark.IR.Prop.Ranges

FreeDec Names' Source # 
Instance details

Defined in Futhark.IR.Aliases

Methods

precomputed :: Names' -> FV -> FV Source #

FreeDec ExpWisdom Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

Methods

precomputed :: ExpWisdom -> FV -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

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

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

Defined in Futhark.IR.Prop.Names

Methods

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

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

Defined in Futhark.IR.Prop.Names

Methods

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

data FV Source #

A computation to build a free variable set.

Instances

Instances details
Semigroup FV Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

(<>) :: FV -> FV -> FV #

sconcat :: NonEmpty FV -> FV #

stimes :: Integral b => b -> FV -> FV #

Monoid FV Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

mempty :: FV #

mappend :: FV -> FV -> FV #

mconcat :: [FV] -> FV #

FreeIn FV Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: FV -> FV Source #

Substitute FV Source # 
Instance details

Defined in Futhark.Transform.Substitute

fvBind :: Names -> FV -> FV Source #

Consider a variable to be bound in the given FV computation.

fvName :: VName -> FV Source #

Take note of a variable reference.

fvNames :: Names -> FV Source #

Take note of a set of variable references.