futhark-0.15.7: An optimising compiler for a functional, array-oriented language.
Safe HaskellNone
LanguageHaskell2010

Futhark.Representation.AST.Attributes.Ranges

Description

Utility declarations for performing range analysis.

Synopsis

Documentation

type Bound = Maybe KnownBound Source #

A possibly undefined bound on a value.

data KnownBound Source #

A known bound on a value.

Constructors

VarBound VName

Has the same bounds as this variable. VERY IMPORTANT: this variable may be an array, so it cannot be immediately translated to a ScalExp.

MinimumBound KnownBound KnownBound

Bounded by the minimum of these two bounds.

MaximumBound KnownBound KnownBound

Bounded by the maximum of these two bounds.

ScalarBound ScalExp

Bounded by this scalar expression.

Instances

Instances details
Eq KnownBound Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Ord KnownBound Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Show KnownBound Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Pretty KnownBound Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

FreeAttr KnownBound Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

FreeIn KnownBound Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Substitute KnownBound Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Rename KnownBound Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

RangeOf Range Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangeOf :: Range -> Range Source #

PrettyAnnot (PatElemT attr) => PrettyAnnot (PatElemT (Range, attr)) Source # 
Instance details

Defined in Futhark.Representation.Ranges

Methods

ppAnnot :: PatElemT (Range, attr) -> Maybe Doc Source #

AliasesOf attr => AliasesOf ([Range], attr) Source # 
Instance details

Defined in Futhark.Representation.Ranges

Methods

aliasesOf :: ([Range], attr) -> Names Source #

AliasesOf attr => AliasesOf (Range, attr) Source # 
Instance details

Defined in Futhark.Representation.Ranges

Methods

aliasesOf :: (Range, attr) -> Names Source #

RangesOf ([Range], attr) Source # 
Instance details

Defined in Futhark.Representation.Ranges

Methods

rangesOf :: ([Range], attr) -> [Range] Source #

RangeOf (Range, attr) Source # 
Instance details

Defined in Futhark.Representation.Ranges

Methods

rangeOf :: (Range, attr) -> Range Source #

boundToScalExp :: KnownBound -> Maybe ScalExp Source #

Convert the bound to a scalar expression if possible. This is possible for all bounds that do not contain VarBounds.

minimumBound :: Bound -> Bound -> Bound Source #

Construct a MinimumBound from two possibly known bounds. The resulting bound will be unknown unless both of the given Bounds are known. This may seem counterintuitive, but it actually makes sense when you consider the task of combining the lower bounds for two different flows of execution (like an if expression). If we only have knowledge about one of the branches, this means that we have no useful information about the combined lower bound, as the other branch may take any value.

maximumBound :: Bound -> Bound -> Bound Source #

Like minimumBound, but constructs a MaximumBound.

type Range = (Bound, Bound) Source #

Upper and lower bound, both inclusive.

unknownRange :: Range Source #

A range in which both upper and lower bounds are 'Nothing.

type ScalExpRange = (Maybe ScalExp, Maybe ScalExp) Source #

The range as a pair of scalar expressions.

type Ranged lore = (Attributes lore, RangedOp (Op lore), RangeOf (LetAttr lore), RangesOf (BodyAttr lore)) Source #

The lore has embedded range information. Note that it may not be up to date, unless whatever maintains the syntax tree is careful.

class RangeOf a where Source #

Something that contains range information.

Methods

rangeOf :: a -> Range Source #

The range of the argument element.

Instances

Instances details
RangeOf SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangeOf :: SubExp -> Range Source #

RangeOf Range Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangeOf :: Range -> Range Source #

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

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangeOf :: PatElemT attr -> Range Source #

RangeOf (Range, attr) Source # 
Instance details

Defined in Futhark.Representation.Ranges

Methods

rangeOf :: (Range, attr) -> Range Source #

RangeOf (VarWisdom, attr) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

Methods

rangeOf :: (VarWisdom, attr) -> Range Source #

class RangesOf a where Source #

Something that contains range information for several things, most notably Body or Pattern.

Methods

rangesOf :: a -> [Range] Source #

The ranges of the argument.

Instances

Instances details
RangeOf a => RangesOf [a] Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangesOf :: [a] -> [Range] Source #

Ranged lore => RangesOf (Body lore) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangesOf :: Body lore -> [Range] Source #

RangeOf attr => RangesOf (PatternT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangesOf :: PatternT attr -> [Range] Source #

RangesOf ([Range], attr) Source # 
Instance details

Defined in Futhark.Representation.Ranges

Methods

rangesOf :: ([Range], attr) -> [Range] Source #

expRanges :: Ranged lore => Exp lore -> [Range] Source #

Ranges of the value parts of the expression.

class IsOp op => RangedOp op where Source #

Methods

opRanges :: op -> [Range] Source #

Instances

Instances details
RangedOp () Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

opRanges :: () -> [Range] Source #

RangedOp SizeOp Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Methods

opRanges :: SizeOp -> [Range] Source #

Ranged inner => RangedOp (SOAC inner) Source # 
Instance details

Defined in Futhark.Representation.SOACS.SOAC

Methods

opRanges :: SOAC inner -> [Range] Source #

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

Defined in Futhark.Representation.Mem

Methods

opRanges :: MemOp inner -> [Range] Source #

(Attributes inner, ASTConstraints lvl) => RangedOp (SegOp lvl inner) Source # 
Instance details

Defined in Futhark.Representation.SegOp

Methods

opRanges :: SegOp lvl inner -> [Range] Source #

(Attributes lore, RangedOp op) => RangedOp (HostOp lore op) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Methods

opRanges :: HostOp lore op -> [Range] Source #

class RangedOp (OpWithRanges op) => CanBeRanged op where Source #

Associated Types

type OpWithRanges op :: Type Source #

Instances

Instances details
CanBeRanged () Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Associated Types

type OpWithRanges () Source #

(Attributes lore, CanBeRanged (Op lore)) => CanBeRanged (SOAC lore) Source # 
Instance details

Defined in Futhark.Representation.SOACS.SOAC

Associated Types

type OpWithRanges (SOAC lore) Source #

Methods

removeOpRanges :: OpWithRanges (SOAC lore) -> SOAC lore Source #

addOpRanges :: SOAC lore -> OpWithRanges (SOAC lore) Source #

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

Defined in Futhark.Representation.Mem

Associated Types

type OpWithRanges (MemOp inner) Source #

Methods

removeOpRanges :: OpWithRanges (MemOp inner) -> MemOp inner Source #

addOpRanges :: MemOp inner -> OpWithRanges (MemOp inner) Source #

(Attributes lore, CanBeRanged (Op lore), ASTConstraints lvl) => CanBeRanged (SegOp lvl lore) Source # 
Instance details

Defined in Futhark.Representation.SegOp

Associated Types

type OpWithRanges (SegOp lvl lore) Source #

Methods

removeOpRanges :: OpWithRanges (SegOp lvl lore) -> SegOp lvl lore Source #

addOpRanges :: SegOp lvl lore -> OpWithRanges (SegOp lvl lore) Source #

(CanBeRanged (Op lore), CanBeRanged op, Attributes lore) => CanBeRanged (HostOp lore op) Source # 
Instance details

Defined in Futhark.Representation.Kernels.Kernel

Associated Types

type OpWithRanges (HostOp lore op) Source #

Methods

removeOpRanges :: OpWithRanges (HostOp lore op) -> HostOp lore op Source #

addOpRanges :: HostOp lore op -> OpWithRanges (HostOp lore op) Source #