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

Safe HaskellNone
LanguageHaskell2010

Futhark.Representation.Ranges

Contents

Description

A representation where all bindings are annotated with range information.

Synopsis

The Lore definition

data Ranges lore Source #

The lore for the basic representation.

Instances
(Annotations lore, CanBeRanged (Op lore)) => Annotations (Ranges lore) Source # 
Instance details

Defined in Futhark.Representation.Ranges

Associated Types

type LetAttr (Ranges lore) :: Type Source #

type ExpAttr (Ranges lore) :: Type Source #

type BodyAttr (Ranges lore) :: Type Source #

type FParamAttr (Ranges lore) :: Type Source #

type LParamAttr (Ranges lore) :: Type Source #

type RetType (Ranges lore) :: Type Source #

type BranchType (Ranges lore) :: Type Source #

type Op (Ranges lore) :: Type Source #

(PrettyLore lore, CanBeRanged (Op lore)) => PrettyLore (Ranges lore) Source # 
Instance details

Defined in Futhark.Representation.Ranges

Methods

ppExpLore :: ExpAttr (Ranges lore) -> Exp (Ranges lore) -> Maybe Doc Source #

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

Defined in Futhark.Representation.Ranges

Methods

expTypesFromPattern :: (HasScope (Ranges lore) m, Monad m) => Pattern (Ranges lore) -> m [BranchType (Ranges lore)] Source #

type LetAttr (Ranges lore) Source # 
Instance details

Defined in Futhark.Representation.Ranges

type LetAttr (Ranges lore) = (Range, LetAttr lore)
type ExpAttr (Ranges lore) Source # 
Instance details

Defined in Futhark.Representation.Ranges

type ExpAttr (Ranges lore) = ExpAttr lore
type BodyAttr (Ranges lore) Source # 
Instance details

Defined in Futhark.Representation.Ranges

type BodyAttr (Ranges lore) = ([Range], BodyAttr lore)
type FParamAttr (Ranges lore) Source # 
Instance details

Defined in Futhark.Representation.Ranges

type FParamAttr (Ranges lore) = FParamAttr lore
type LParamAttr (Ranges lore) Source # 
Instance details

Defined in Futhark.Representation.Ranges

type LParamAttr (Ranges lore) = LParamAttr lore
type RetType (Ranges lore) Source # 
Instance details

Defined in Futhark.Representation.Ranges

type RetType (Ranges lore) = RetType lore
type BranchType (Ranges lore) Source # 
Instance details

Defined in Futhark.Representation.Ranges

type BranchType (Ranges lore) = BranchType lore
type Op (Ranges lore) Source # 
Instance details

Defined in Futhark.Representation.Ranges

type Op (Ranges lore) = OpWithRanges (Op lore)

Module re-exports

Adding ranges

addRangesToPattern :: (Attributes lore, CanBeRanged (Op lore)) => Pattern lore -> Exp (Ranges lore) -> Pattern (Ranges lore) Source #

mkRangedLetStm :: (Attributes lore, CanBeRanged (Op lore)) => Pattern lore -> ExpAttr lore -> Exp (Ranges lore) -> Stm (Ranges lore) Source #

mkRangedBody :: BodyAttr lore -> Stms (Ranges lore) -> Result -> Body (Ranges lore) Source #

mkPatternRanges :: (Attributes lore, CanBeRanged (Op lore)) => Pattern lore -> Exp (Ranges lore) -> ([PatElemT (Range, LetAttr lore)], [PatElemT (Range, LetAttr lore)]) Source #

Removing ranges

removeProgRanges :: CanBeRanged (Op lore) => Prog (Ranges lore) -> Prog lore Source #

removeExpRanges :: CanBeRanged (Op lore) => Exp (Ranges lore) -> Exp lore Source #

removeBodyRanges :: CanBeRanged (Op lore) => Body (Ranges lore) -> Body lore Source #

removeStmRanges :: CanBeRanged (Op lore) => Stm (Ranges lore) -> Stm lore Source #

Orphan instances

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

Methods

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

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

Methods

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

RangeOf (Range, attr) Source # 
Instance details

Methods

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