| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Futhark.IR.Aliases
Description
A representation where all patterns are annotated with aliasing information. It also records consumption of variables in bodies.
Note that this module is mostly not concerned with actually computing the aliasing information; only with shuffling it around and providing some basic building blocks. See modules such as Futhark.Analysis.Alias for computing the aliases in the first place.
Synopsis
- data Aliases rep
- newtype AliasDec = AliasDec {}
- type VarAliases = AliasDec
- type ConsumedInExp = AliasDec
- type BodyAliasing = ([VarAliases], ConsumedInExp)
- module Futhark.IR.Prop.Aliases
- module Futhark.IR.Prop
- module Futhark.IR.Traversals
- module Futhark.IR.Pretty
- module Futhark.IR.Syntax
- mkAliasedBody :: (ASTRep rep, CanBeAliased (Op rep)) => BodyDec rep -> Stms (Aliases rep) -> Result -> Body (Aliases rep)
- mkAliasedPat :: (Aliased rep, Typed dec) => Pat dec -> Exp rep -> Pat (VarAliases, dec)
- mkBodyAliasing :: Aliased rep => Stms rep -> Result -> BodyAliasing
- removeProgAliases :: CanBeAliased (Op rep) => Prog (Aliases rep) -> Prog rep
- removeFunDefAliases :: CanBeAliased (Op rep) => FunDef (Aliases rep) -> FunDef rep
- removeExpAliases :: CanBeAliased (Op rep) => Exp (Aliases rep) -> Exp rep
- removeStmAliases :: CanBeAliased (Op rep) => Stm (Aliases rep) -> Stm rep
- removeBodyAliases :: CanBeAliased (Op rep) => Body (Aliases rep) -> Body rep
- removeLambdaAliases :: CanBeAliased (Op rep) => Lambda (Aliases rep) -> Lambda rep
- removePatAliases :: Pat (AliasDec, a) -> Pat a
- removeScopeAliases :: Scope (Aliases rep) -> Scope rep
- type AliasesAndConsumed = (Map VName Names, Names)
- trackAliases :: Aliased rep => AliasesAndConsumed -> Stm rep -> AliasesAndConsumed
- mkStmsAliases :: Aliased rep => Stms rep -> Result -> ([Names], Names)
- consumedInStms :: Aliased rep => Stms rep -> Names
The representation definition
The rep for the basic representation.
Instances
A wrapper around AliasDec to get around the fact that we need an
 Ord instance, which 'AliasDec does not have.
Instances
| Monoid AliasDec Source # | |
| Semigroup AliasDec Source # | |
| Show AliasDec Source # | |
| FreeDec AliasDec Source # | |
| Defined in Futhark.IR.Aliases | |
| FreeIn AliasDec Source # | |
| Rename AliasDec Source # | |
| Substitute AliasDec Source # | |
| Defined in Futhark.IR.Aliases | |
| Eq AliasDec Source # | |
| Ord AliasDec Source # | |
| Defined in Futhark.IR.Aliases | |
| Pretty AliasDec Source # | |
| Defined in Futhark.IR.Aliases | |
| AliasesOf (VarAliases, dec) Source # | |
| Defined in Futhark.IR.Aliases Methods aliasesOf :: (VarAliases, dec) -> Names Source # | |
type VarAliases = AliasDec Source #
The aliases of the let-bound variable.
type ConsumedInExp = AliasDec Source #
Everything consumed in the expression.
type BodyAliasing = ([VarAliases], ConsumedInExp) Source #
The aliases of what is returned by the Body, and what is
 consumed inside of it.
module Futhark.IR.Prop.Aliases
Module re-exports
module Futhark.IR.Prop
module Futhark.IR.Traversals
module Futhark.IR.Pretty
module Futhark.IR.Syntax
Adding aliases
mkAliasedBody :: (ASTRep rep, CanBeAliased (Op rep)) => BodyDec rep -> Stms (Aliases rep) -> Result -> Body (Aliases rep) Source #
Augment a body decoration with aliasing information provided by the statements and result of that body.
mkAliasedPat :: (Aliased rep, Typed dec) => Pat dec -> Exp rep -> Pat (VarAliases, dec) Source #
Augment a pattern with aliasing information provided by the expression the pattern is bound to.
mkBodyAliasing :: Aliased rep => Stms rep -> Result -> BodyAliasing Source #
Given statements (with aliasing information) and a body result, produce aliasing information for the corresponding body as a whole. This is basically just looking up the aliasing of each element of the result, and removing the names that are no longer in scope. Note that this does *not* include aliases of results that are not bound in the statements!
Removing aliases
removeProgAliases :: CanBeAliased (Op rep) => Prog (Aliases rep) -> Prog rep Source #
Remove alias information from a program.
removeFunDefAliases :: CanBeAliased (Op rep) => FunDef (Aliases rep) -> FunDef rep Source #
Remove alias information from a function.
removeExpAliases :: CanBeAliased (Op rep) => Exp (Aliases rep) -> Exp rep Source #
Remove alias information from an expression.
removeStmAliases :: CanBeAliased (Op rep) => Stm (Aliases rep) -> Stm rep Source #
Remove alias information from statements.
removeBodyAliases :: CanBeAliased (Op rep) => Body (Aliases rep) -> Body rep Source #
Remove alias information from body.
removeLambdaAliases :: CanBeAliased (Op rep) => Lambda (Aliases rep) -> Lambda rep Source #
Remove alias information from lambda.
removeScopeAliases :: Scope (Aliases rep) -> Scope rep Source #
Remove alias information from an aliased scope.
Tracking aliases
type AliasesAndConsumed = (Map VName Names, Names) Source #
A tuple of a mapping from variable names to their aliases, and the names of consumed variables.
trackAliases :: Aliased rep => AliasesAndConsumed -> Stm rep -> AliasesAndConsumed Source #
A helper function for computing the aliases of a sequence of
 statements.  You'd use this while recursing down the statements
 from first to last.  The AliasesAndConsumed parameter is the
 current "state" of aliasing, and the function then returns a new
 state.  The main thing this function provides is proper handling of
 transitivity and "reverse" aliases.