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

Futhark.IR.Syntax

Description

Definition of the Futhark core language IR

For actually constructing ASTs, see Futhark.Construct.

Types and values

The core language type system is much more restricted than the core language. This is a theme that repeats often. The only types that are supported in the core language are various primitive types PrimType which can be combined in arrays (ignore Mem and Acc for now). Types are represented as TypeBase, which is parameterised by the shape of the array and whether we keep uniqueness information. The Type alias, which is the most commonly used, uses Shape and NoUniqueness.

This means that the records, tuples, and sum types of the source language are represented merely as collections of primitives and arrays. This is implemented in Futhark.Internalise, but the specifics are not important for writing passes on the core language. What is important is that many constructs that conceptually return tuples instead return multiple values. This is not merely syntactic sugar for a tuple: each of those values are eventually bound to distinct variables. The prettyprinter for the IR will typically print such collections of values or types in curly braces.

The system of primitive types is interesting in itself. See Futhark.IR.Primitive.

Overall AST design

Internally, the Futhark compiler core intermediate representation resembles a traditional compiler for an imperative language more than it resembles, say, a Haskell or ML compiler. All functions are monomorphic (except for sizes), first-order, and defined at the top level. Notably, the IR does not use continuation-passing style (CPS) at any time. Instead it uses Administrative Normal Form (ANF), where all subexpressions SubExp are either constants PrimValue or variables VName. Variables are represented as a human-readable Name (which doesn't matter to the compiler) as well as a numeric tag, which is what the compiler actually looks at. All variable names when prettyprinted are of the form foo_123. Function names are just Names, though.

The body of a function (FunDef) is a Body, which consists of a sequence of statements (Stms) and a Result. Execution of a Body consists of executing all of the statements, then returning the values of the variables indicated by the result.

A statement (Stm) consists of a Pat alongside an expression Exp. A pattern is a sequence of name/type pairs.

For example, the source language expression let z = x + y - 1 in z would in the core language be represented (in prettyprinted form) as something like:

let {a_12} = x_10 + y_11
let {b_13} = a_12 - 1
in {b_13}

Representations

Most AST types (Stm, Exp, Prog, etc) are parameterised by a type parameter rep. The representation specifies how to fill out various polymorphic parts of the AST. For example, Exp has a constructor Op whose payload depends on rep, via the use of a type family called Op (a kind of type-level function) which is applied to the rep. The SOACS representation (Futhark.IR.SOACS) thus uses a rep called SOACS, and defines that Op SOACS is a SOAC, while the Kernels representation (Futhark.IR.Kernels) defines Op Kernels as some kind of kernel construct. Similarly, various other decorations (e.g. what information we store in a PatElem) are also type families.

The full list of possible decorations is defined as part of the type class RepTypes (although other type families are also used elsewhere in the compiler on an ad hoc basis).

Essentially, the rep type parameter functions as a kind of proxy, saving us from having to parameterise the AST type with all the different forms of decorations that we desire (it would easily become a type with a dozen type parameters).

Some AST elements (such as Pat) do not take a rep type parameter, but instead immediately the single type of decoration that they contain. We only use the more complicated machinery when needed.

Defining a new representation (or rep) thus requires you to define an empty datatype and implement a handful of type class instances for it. See the source of Futhark.IR.Seq for what is likely the simplest example.

Synopsis

Documentation

pretty :: Pretty a => a -> String Source #

Prettyprint a value, wrapped to 80 characters.

Types

data Uniqueness Source #

The uniqueness attribute of a type. This essentially indicates whether or not in-place modifications are acceptable. With respect to ordering, Unique is greater than Nonunique.

Constructors

Nonunique

May have references outside current function.

Unique

No references outside current function.

Instances

Instances details
Eq Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Ord Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Show Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Semigroup Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Monoid Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Pretty Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: DeclType -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.IR.Mem

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.IR.Mem

FixExt ret => DeclExtTyped (MemInfo ExtSize Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

DeclTyped (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

data NoUniqueness Source #

A fancier name for () - encodes no uniqueness information.

Constructors

NoUniqueness 

Instances

Instances details
Eq NoUniqueness Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Ord NoUniqueness Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Show NoUniqueness Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Semigroup NoUniqueness Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Monoid NoUniqueness Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Pretty NoUniqueness Source # 
Instance details

Defined in Futhark.IR.Pretty

SetType Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

setType :: Type -> Type -> Type Source #

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Typed Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Type -> Type Source #

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.IR.Mem

HasLetDecMem LetDecMem Source # 
Instance details

Defined in Futhark.IR.Mem

FixExt ret => ExtTyped (MemInfo ExtSize NoUniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

Typed (MemInfo SubExp NoUniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

newtype Rank Source #

The size of an array type as merely the number of dimensions, with no further information.

Constructors

Rank Int 

Instances

Instances details
Eq Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

compare :: Rank -> Rank -> Ordering #

(<) :: Rank -> Rank -> Bool #

(<=) :: Rank -> Rank -> Bool #

(>) :: Rank -> Rank -> Bool #

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

max :: Rank -> Rank -> Rank #

min :: Rank -> Rank -> Rank #

Show Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Rank -> ShowS #

show :: Rank -> String #

showList :: [Rank] -> ShowS #

Semigroup Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

(<>) :: Rank -> Rank -> Rank #

sconcat :: NonEmpty Rank -> Rank #

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

Monoid Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

mempty :: Rank #

mappend :: Rank -> Rank -> Rank #

mconcat :: [Rank] -> Rank #

ArrayShape Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Substitute Rank Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename Rank Source # 
Instance details

Defined in Futhark.Transform.Rename

Pretty u => Pretty (TypeBase Rank u) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: TypeBase Rank u -> Doc #

pprPrec :: Int -> TypeBase Rank u -> Doc #

pprList :: [TypeBase Rank u] -> Doc #

class (Monoid a, Eq a, Ord a) => ArrayShape a where Source #

A class encompassing types containing array shape information.

Methods

shapeRank :: a -> Int Source #

Return the rank of an array with the given size.

subShapeOf :: a -> a -> Bool Source #

Check whether one shape if a subset of another shape.

data Space Source #

The memory space of a block. If DefaultSpace, this is the "default" space, whatever that is. The exact meaning of the SpaceId depends on the backend used. In GPU kernels, for example, this is used to distinguish between constant, global and shared memory spaces. In GPU-enabled host code, it is used to distinguish between host memory (DefaultSpace) and GPU space.

Constructors

DefaultSpace 
Space SpaceId 
ScalarSpace [SubExp] PrimType

A special kind of memory that is a statically sized array of some primitive type. Used for private memory on GPUs.

Instances

Instances details
Eq Space Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord Space Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

compare :: Space -> Space -> Ordering #

(<) :: Space -> Space -> Bool #

(<=) :: Space -> Space -> Bool #

(>) :: Space -> Space -> Bool #

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

max :: Space -> Space -> Space #

min :: Space -> Space -> Space #

Show Space Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Space -> ShowS #

show :: Space -> String #

showList :: [Space] -> ShowS #

Pretty Space Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Space -> Doc #

pprPrec :: Int -> Space -> Doc #

pprList :: [Space] -> Doc #

FreeIn Space Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Space -> FV Source #

Simplifiable Space Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

data TypeBase shape u Source #

The type of a value. When comparing types for equality with ==, shapes must match.

Constructors

Prim PrimType 
Acc VName Shape [Type] u

Token, index space, element type, and uniqueness.

Array PrimType shape u 
Mem Space 

Instances

Instances details
Bifunctor TypeBase Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

bimap :: (a -> b) -> (c -> d) -> TypeBase a c -> TypeBase b d #

first :: (a -> b) -> TypeBase a c -> TypeBase b c #

second :: (b -> c) -> TypeBase a b -> TypeBase a c #

Bitraversable TypeBase Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> TypeBase a b -> f (TypeBase c d) #

Bifoldable TypeBase Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

bifold :: Monoid m => TypeBase m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> TypeBase a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> TypeBase a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> TypeBase a b -> c #

SetType Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

setType :: Type -> Type -> Type Source #

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Type -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.IR.RetType

(Eq u, Eq shape) => Eq (TypeBase shape u) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

(==) :: TypeBase shape u -> TypeBase shape u -> Bool #

(/=) :: TypeBase shape u -> TypeBase shape u -> Bool #

(Ord u, Ord shape) => Ord (TypeBase shape u) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

compare :: TypeBase shape u -> TypeBase shape u -> Ordering #

(<) :: TypeBase shape u -> TypeBase shape u -> Bool #

(<=) :: TypeBase shape u -> TypeBase shape u -> Bool #

(>) :: TypeBase shape u -> TypeBase shape u -> Bool #

(>=) :: TypeBase shape u -> TypeBase shape u -> Bool #

max :: TypeBase shape u -> TypeBase shape u -> TypeBase shape u #

min :: TypeBase shape u -> TypeBase shape u -> TypeBase shape u #

(Show u, Show shape) => Show (TypeBase shape u) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> TypeBase shape u -> ShowS #

show :: TypeBase shape u -> String #

showList :: [TypeBase shape u] -> ShowS #

Pretty u => Pretty (TypeBase Rank u) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: TypeBase Rank u -> Doc #

pprPrec :: Int -> TypeBase Rank u -> Doc #

pprList :: [TypeBase Rank u] -> Doc #

Pretty u => Pretty (TypeBase ExtShape u) Source # 
Instance details

Defined in Futhark.IR.Pretty

Pretty u => Pretty (TypeBase Shape u) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: TypeBase Shape u -> Doc #

pprPrec :: Int -> TypeBase Shape u -> Doc #

pprList :: [TypeBase Shape u] -> Doc #

(FixExt shape, ArrayShape shape) => FixExt (TypeBase shape u) Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

fixExt :: Int -> SubExp -> TypeBase shape u -> TypeBase shape u Source #

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

Defined in Futhark.IR.Prop.Names

Methods

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

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

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> TypeBase shape u -> TypeBase shape u Source #

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

Defined in Futhark.Transform.Rename

Methods

rename :: TypeBase shape u -> RenameM (TypeBase shape u) Source #

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

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: SimplifiableRep rep => TypeBase shape u -> SimpleM rep (TypeBase shape u) Source #

data Diet Source #

Information about which parts of a value/type are consumed. For example, we might say that a function taking three arguments of types ([int], *[int], [int]) has diet [Observe, Consume, Observe].

Constructors

Consume

Consumes this value.

Observe

Only observes value in this position, does not consume. A result may alias this.

ObservePrim

As Observe, but the result will not alias, because the parameter does not carry aliases.

Instances

Instances details
Eq Diet Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord Diet Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

compare :: Diet -> Diet -> Ordering #

(<) :: Diet -> Diet -> Bool #

(<=) :: Diet -> Diet -> Bool #

(>) :: Diet -> Diet -> Bool #

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

max :: Diet -> Diet -> Diet #

min :: Diet -> Diet -> Diet #

Show Diet Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Diet -> ShowS #

show :: Diet -> String #

showList :: [Diet] -> ShowS #

Abstract syntax tree

data Ident Source #

An identifier consists of its name and the type of the value bound to the identifier.

Constructors

Ident 

Fields

Instances

Instances details
Eq Ident Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord Ident Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

compare :: Ident -> Ident -> Ordering #

(<) :: Ident -> Ident -> Bool #

(<=) :: Ident -> Ident -> Bool #

(>) :: Ident -> Ident -> Bool #

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

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

Show Ident Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Pretty Ident Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Ident -> Doc #

pprPrec :: Int -> Ident -> Doc #

pprList :: [Ident] -> Doc #

Typed Ident Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Ident -> Type Source #

FreeIn Ident Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Ident -> FV Source #

Substitute Ident Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename Ident Source # 
Instance details

Defined in Futhark.Transform.Rename

data SubExp Source #

A subexpression is either a scalar constant or a variable. One important property is that evaluation of a subexpression is guaranteed to complete in constant time.

Constructors

Constant PrimValue 
Var VName 

Instances

Instances details
Eq SubExp Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord SubExp Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Show SubExp Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

ToExp SubExp Source # 
Instance details

Defined in Futhark.CodeGen.Backends.SimpleRep

Methods

toExp :: SubExp -> SrcLoc -> Exp #

Pretty SubExp Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: SubExp -> Doc #

pprPrec :: Int -> SubExp -> Doc #

pprList :: [SubExp] -> Doc #

Pretty ExtShape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: ExtShape -> Doc #

pprPrec :: Int -> ExtShape -> Doc #

pprList :: [ExtShape] -> Doc #

Pretty Shape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Shape -> Doc #

pprPrec :: Int -> Shape -> Doc #

pprList :: [Shape] -> Doc #

FixExt ExtSize Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

fixExt :: Int -> SubExp -> ExtSize -> ExtSize Source #

SetType Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

setType :: Type -> Type -> Type Source #

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Type -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.IR.Mem

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.IR.Mem

FreeIn SubExp Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: SubExp -> FV Source #

Substitute SubExp Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename SubExp Source # 
Instance details

Defined in Futhark.Transform.Rename

Rename ExtSize Source # 
Instance details

Defined in Futhark.Transform.Rename

ToExp SubExp Source # 
Instance details

Defined in Futhark.Construct

Methods

toExp :: MonadBuilder m => SubExp -> m (Exp (Rep m)) Source #

Simplifiable SubExp Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Simplifiable ExtSize Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

HasLetDecMem LetDecMem Source # 
Instance details

Defined in Futhark.IR.Mem

ToExp SubExp Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

ArrayShape (ShapeBase SubExp) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

ArrayShape (ShapeBase ExtSize) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.IR.Mem

Pretty u => Pretty (TypeBase ExtShape u) Source # 
Instance details

Defined in Futhark.IR.Pretty

Pretty u => Pretty (TypeBase Shape u) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: TypeBase Shape u -> Doc #

pprPrec :: Int -> TypeBase Shape u -> Doc #

pprList :: [TypeBase Shape u] -> Doc #

FixExt ret => FixExt (MemInfo ExtSize u ret) Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

fixExt :: Int -> SubExp -> MemInfo ExtSize u ret -> MemInfo ExtSize u ret Source #

FixExt ret => DeclExtTyped (MemInfo ExtSize Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

FixExt ret => ExtTyped (MemInfo ExtSize NoUniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

DeclTyped (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

Typed (MemInfo SubExp NoUniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

data PatElem dec Source #

An element of a pattern - consisting of a name and an addditional parametric decoration. This decoration is what is expected to contain the type of the resulting variable.

Constructors

PatElem 

Fields

Instances

Instances details
Functor PatElem Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

fmap :: (a -> b) -> PatElem a -> PatElem b #

(<$) :: a -> PatElem b -> PatElem a #

Foldable PatElem Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

fold :: Monoid m => PatElem m -> m #

foldMap :: Monoid m => (a -> m) -> PatElem a -> m #

foldMap' :: Monoid m => (a -> m) -> PatElem a -> m #

foldr :: (a -> b -> b) -> b -> PatElem a -> b #

foldr' :: (a -> b -> b) -> b -> PatElem a -> b #

foldl :: (b -> a -> b) -> b -> PatElem a -> b #

foldl' :: (b -> a -> b) -> b -> PatElem a -> b #

foldr1 :: (a -> a -> a) -> PatElem a -> a #

foldl1 :: (a -> a -> a) -> PatElem a -> a #

toList :: PatElem a -> [a] #

null :: PatElem a -> Bool #

length :: PatElem a -> Int #

elem :: Eq a => a -> PatElem a -> Bool #

maximum :: Ord a => PatElem a -> a #

minimum :: Ord a => PatElem a -> a #

sum :: Num a => PatElem a -> a #

product :: Num a => PatElem a -> a #

Traversable PatElem Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

traverse :: Applicative f => (a -> f b) -> PatElem a -> f (PatElem b) #

sequenceA :: Applicative f => PatElem (f a) -> f (PatElem a) #

mapM :: Monad m => (a -> m b) -> PatElem a -> m (PatElem b) #

sequence :: Monad m => PatElem (m a) -> m (PatElem a) #

Eq dec => Eq (PatElem dec) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

(==) :: PatElem dec -> PatElem dec -> Bool #

(/=) :: PatElem dec -> PatElem dec -> Bool #

Ord dec => Ord (PatElem dec) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

compare :: PatElem dec -> PatElem dec -> Ordering #

(<) :: PatElem dec -> PatElem dec -> Bool #

(<=) :: PatElem dec -> PatElem dec -> Bool #

(>) :: PatElem dec -> PatElem dec -> Bool #

(>=) :: PatElem dec -> PatElem dec -> Bool #

max :: PatElem dec -> PatElem dec -> PatElem dec #

min :: PatElem dec -> PatElem dec -> PatElem dec #

Show dec => Show (PatElem dec) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> PatElem dec -> ShowS #

show :: PatElem dec -> String #

showList :: [PatElem dec] -> ShowS #

Pretty t => Pretty (PatElem t) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: PatElem t -> Doc #

pprPrec :: Int -> PatElem t -> Doc #

pprList :: [PatElem t] -> Doc #

SetType dec => SetType (PatElem dec) Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

setType :: PatElem dec -> Type -> PatElem dec Source #

Typed dec => Typed (PatElem dec) Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: PatElem dec -> Type Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: PatElem dec -> FV Source #

Substitute dec => Substitute (PatElem dec) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename dec => Rename (PatElem dec) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: PatElem dec -> RenameM (PatElem dec) Source #

AliasesOf dec => AliasesOf (PatElem dec) Source # 
Instance details

Defined in Futhark.IR.Prop.Aliases

Methods

aliasesOf :: PatElem dec -> Names Source #

newtype Pat dec Source #

A pattern is conceptually just a list of names and their types.

Constructors

Pat 

Fields

Instances

Instances details
Functor Pat Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

fmap :: (a -> b) -> Pat a -> Pat b #

(<$) :: a -> Pat b -> Pat a #

Foldable Pat Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

fold :: Monoid m => Pat m -> m #

foldMap :: Monoid m => (a -> m) -> Pat a -> m #

foldMap' :: Monoid m => (a -> m) -> Pat a -> m #

foldr :: (a -> b -> b) -> b -> Pat a -> b #

foldr' :: (a -> b -> b) -> b -> Pat a -> b #

foldl :: (b -> a -> b) -> b -> Pat a -> b #

foldl' :: (b -> a -> b) -> b -> Pat a -> b #

foldr1 :: (a -> a -> a) -> Pat a -> a #

foldl1 :: (a -> a -> a) -> Pat a -> a #

toList :: Pat a -> [a] #

null :: Pat a -> Bool #

length :: Pat a -> Int #

elem :: Eq a => a -> Pat a -> Bool #

maximum :: Ord a => Pat a -> a #

minimum :: Ord a => Pat a -> a #

sum :: Num a => Pat a -> a #

product :: Num a => Pat a -> a #

Traversable Pat Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

traverse :: Applicative f => (a -> f b) -> Pat a -> f (Pat b) #

sequenceA :: Applicative f => Pat (f a) -> f (Pat a) #

mapM :: Monad m => (a -> m b) -> Pat a -> m (Pat b) #

sequence :: Monad m => Pat (m a) -> m (Pat a) #

Eq dec => Eq (Pat dec) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: Pat dec -> Pat dec -> Bool #

(/=) :: Pat dec -> Pat dec -> Bool #

Ord dec => Ord (Pat dec) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Pat dec -> Pat dec -> Ordering #

(<) :: Pat dec -> Pat dec -> Bool #

(<=) :: Pat dec -> Pat dec -> Bool #

(>) :: Pat dec -> Pat dec -> Bool #

(>=) :: Pat dec -> Pat dec -> Bool #

max :: Pat dec -> Pat dec -> Pat dec #

min :: Pat dec -> Pat dec -> Pat dec #

Show dec => Show (Pat dec) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> Pat dec -> ShowS #

show :: Pat dec -> String #

showList :: [Pat dec] -> ShowS #

Semigroup (Pat dec) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(<>) :: Pat dec -> Pat dec -> Pat dec #

sconcat :: NonEmpty (Pat dec) -> Pat dec #

stimes :: Integral b => b -> Pat dec -> Pat dec #

Monoid (Pat dec) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

mempty :: Pat dec #

mappend :: Pat dec -> Pat dec -> Pat dec #

mconcat :: [Pat dec] -> Pat dec #

Pretty t => Pretty (Pat t) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Pat t -> Doc #

pprPrec :: Int -> Pat t -> Doc #

pprList :: [Pat t] -> Doc #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Pat dec -> FV Source #

Substitute dec => Substitute (Pat dec) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Pat dec -> Pat dec Source #

Rename dec => Rename (Pat dec) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Pat dec -> RenameM (Pat dec) Source #

data StmAux dec Source #

Auxilliary Information associated with a statement.

Constructors

StmAux 

Fields

Instances

Instances details
Eq dec => Eq (StmAux dec) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: StmAux dec -> StmAux dec -> Bool #

(/=) :: StmAux dec -> StmAux dec -> Bool #

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

Defined in Futhark.IR.Syntax

Methods

compare :: StmAux dec -> StmAux dec -> Ordering #

(<) :: StmAux dec -> StmAux dec -> Bool #

(<=) :: StmAux dec -> StmAux dec -> Bool #

(>) :: StmAux dec -> StmAux dec -> Bool #

(>=) :: StmAux dec -> StmAux dec -> Bool #

max :: StmAux dec -> StmAux dec -> StmAux dec #

min :: StmAux dec -> StmAux dec -> StmAux dec #

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

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> StmAux dec -> ShowS #

show :: StmAux dec -> String #

showList :: [StmAux dec] -> ShowS #

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

Defined in Futhark.IR.Syntax

Methods

(<>) :: StmAux dec -> StmAux dec -> StmAux dec #

sconcat :: NonEmpty (StmAux dec) -> StmAux dec #

stimes :: Integral b => b -> StmAux dec -> StmAux dec #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: StmAux dec -> FV Source #

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

Defined in Futhark.Transform.Substitute

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

Defined in Futhark.Transform.Rename

Methods

rename :: StmAux dec -> RenameM (StmAux dec) Source #

data Stm rep Source #

A local variable binding.

Constructors

Let 

Fields

Instances

Instances details
Scoped rep (Stm rep) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: Stm rep -> Scope rep Source #

Scoped rep (Stms rep) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: Stms rep -> Scope rep Source #

RepTypes rep => Eq (Stm rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: Stm rep -> Stm rep -> Bool #

(/=) :: Stm rep -> Stm rep -> Bool #

RepTypes rep => Ord (Stm rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Stm rep -> Stm rep -> Ordering #

(<) :: Stm rep -> Stm rep -> Bool #

(<=) :: Stm rep -> Stm rep -> Bool #

(>) :: Stm rep -> Stm rep -> Bool #

(>=) :: Stm rep -> Stm rep -> Bool #

max :: Stm rep -> Stm rep -> Stm rep #

min :: Stm rep -> Stm rep -> Stm rep #

RepTypes rep => Show (Stm rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> Stm rep -> ShowS #

show :: Stm rep -> String #

showList :: [Stm rep] -> ShowS #

PrettyRep rep => Pretty (Stms rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Stms rep -> Doc #

pprPrec :: Int -> Stms rep -> Doc #

pprList :: [Stms rep] -> Doc #

PrettyRep rep => Pretty (Stm rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Stm rep -> Doc #

pprPrec :: Int -> Stm rep -> Doc #

pprList :: [Stm rep] -> Doc #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Stms rep -> FV Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Stm rep -> FV Source #

Substitute (Stm rep) => Substitute (Stms rep) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Stms rep -> Stms rep Source #

Substitutable rep => Substitute (Stm rep) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Stm rep -> Stm rep Source #

Renameable rep => Rename (Stm rep) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Stm rep -> RenameM (Stm rep) Source #

type Stms rep = Seq (Stm rep) Source #

A sequence of statements.

data SubExpRes Source #

A pairing of a subexpression and some certificates.

Constructors

SubExpRes 

Instances

Instances details
Eq SubExpRes Source # 
Instance details

Defined in Futhark.IR.Syntax

Ord SubExpRes Source # 
Instance details

Defined in Futhark.IR.Syntax

Show SubExpRes Source # 
Instance details

Defined in Futhark.IR.Syntax

Pretty SubExpRes Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: SubExpRes -> Doc #

pprPrec :: Int -> SubExpRes -> Doc #

pprList :: [SubExpRes] -> Doc #

FreeIn SubExpRes Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: SubExpRes -> FV Source #

Substitute SubExpRes Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename SubExpRes Source # 
Instance details

Defined in Futhark.Transform.Rename

Simplifiable SubExpRes Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

type Result = [SubExpRes] Source #

The result of a body is a sequence of subexpressions.

data Body rep Source #

A body consists of a number of bindings, terminating in a result (essentially a tuple literal).

Constructors

Body 

Fields

Instances

Instances details
RepTypes rep => Eq (Body rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: Body rep -> Body rep -> Bool #

(/=) :: Body rep -> Body rep -> Bool #

RepTypes rep => Ord (Body rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Body rep -> Body rep -> Ordering #

(<) :: Body rep -> Body rep -> Bool #

(<=) :: Body rep -> Body rep -> Bool #

(>) :: Body rep -> Body rep -> Bool #

(>=) :: Body rep -> Body rep -> Bool #

max :: Body rep -> Body rep -> Body rep #

min :: Body rep -> Body rep -> Body rep #

RepTypes rep => Show (Body rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> Body rep -> ShowS #

show :: Body rep -> String #

showList :: [Body rep] -> ShowS #

PrettyRep rep => Pretty (Body rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Body rep -> Doc #

pprPrec :: Int -> Body rep -> Doc #

pprList :: [Body rep] -> Doc #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Body rep -> FV Source #

Substitutable rep => Substitute (Body rep) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Body rep -> Body rep Source #

Renameable rep => Rename (Body rep) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Body rep -> RenameM (Body rep) Source #

data BasicOp Source #

A primitive operation that returns something of known size and does not itself contain any bindings.

Constructors

SubExp SubExp

A variable or constant.

Opaque OpaqueOp SubExp

Semantically and operationally just identity, but is invisible/impenetrable to optimisations (hopefully). This partially a hack to avoid optimisation (so, to work around compiler limitations), but is also used to implement tracing and other operations that are semantically invisible, but have some sort of effect (brrr).

ArrayLit [SubExp] Type

Array literals, e.g., [ [1+x, 3], [2, 1+4] ]. Second arg is the element type of the rows of the array.

UnOp UnOp SubExp

Unary operation.

BinOp BinOp SubExp SubExp

Binary operation.

CmpOp CmpOp SubExp SubExp

Comparison - result type is always boolean.

ConvOp ConvOp SubExp

Conversion "casting".

Assert SubExp (ErrorMsg SubExp) (SrcLoc, [SrcLoc])

Turn a boolean into a certificate, halting the program with the given error message if the boolean is false.

Index VName (Slice SubExp)

The certificates for bounds-checking are part of the Stm.

Update Safety VName (Slice SubExp) SubExp

An in-place update of the given array at the given position. Consumes the array. If Safe, perform a run-time bounds check and ignore the write if out of bounds (like Scatter).

FlatIndex VName (FlatSlice SubExp) 
FlatUpdate VName (FlatSlice SubExp) VName 
Concat Int (NonEmpty VName) SubExp
concat(0, [1] :| [[2, 3, 4], [5, 6]], 6) = [1, 2, 3, 4, 5, 6]@.

Concatenates the non-empty list of VName resulting in an array of length SubExp. The Int argument is used to specify the dimension along which the arrays are concatenated. For instance:

concat(1, [[1,2], [3, 4]] :| [[[5,6]], [[7, 8]]], 4) = [[1, 2, 5, 6], [3, 4, 7, 8]]
Copy VName

Copy the given array. The result will not alias anything.

Manifest [Int] VName

Manifest an array with dimensions represented in the given order. The result will not alias anything.

Iota SubExp SubExp SubExp IntType

iota(n, x, s) = [x,x+s,..,x+(n-1)*s].

The IntType indicates the type of the array returned and the offset/stride arguments, but not the length argument.

Replicate Shape SubExp
replicate([3][2],1) = [[1,1], [1,1], [1,1]]
Scratch PrimType [SubExp]

Create array of given type and shape, with undefined elements.

Reshape (ShapeChange SubExp) VName

1st arg is the new shape, 2nd arg is the input array.

Rearrange [Int] VName

Permute the dimensions of the input array. The list of integers is a list of dimensions (0-indexed), which must be a permutation of [0,n-1], where n is the number of dimensions in the input array.

Rotate [SubExp] VName

Rotate the dimensions of the input array. The list of subexpressions specify how much each dimension is rotated. The length of this list must be equal to the rank of the array.

UpdateAcc VName [SubExp] [SubExp]

Update an accumulator at the given index with the given value. Consumes the accumulator and produces a new one.

Instances

Instances details
Eq BasicOp Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

Ord BasicOp Source # 
Instance details

Defined in Futhark.IR.Syntax

Show BasicOp Source # 
Instance details

Defined in Futhark.IR.Syntax

Pretty BasicOp Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: BasicOp -> Doc #

pprPrec :: Int -> BasicOp -> Doc #

pprList :: [BasicOp] -> Doc #

data UnOp Source #

Various unary operators. It is a bit ad-hoc what is a unary operator and what is a built-in function. Perhaps these should all go away eventually.

Constructors

Not

E.g., ! True == False.

Complement IntType

E.g., ~(~1) = 1.

Abs IntType

abs(-2) = 2.

FAbs FloatType

fabs(-2.0) = 2.0.

SSignum IntType

Signed sign function: ssignum(-2) = -1.

USignum IntType

Unsigned sign function: usignum(2) = 1.

FSignum FloatType

Floating-point sign function.

Instances

Instances details
Eq UnOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

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

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

Ord UnOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

compare :: UnOp -> UnOp -> Ordering #

(<) :: UnOp -> UnOp -> Bool #

(<=) :: UnOp -> UnOp -> Bool #

(>) :: UnOp -> UnOp -> Bool #

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

max :: UnOp -> UnOp -> UnOp #

min :: UnOp -> UnOp -> UnOp #

Show UnOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

showsPrec :: Int -> UnOp -> ShowS #

show :: UnOp -> String #

showList :: [UnOp] -> ShowS #

Pretty UnOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

ppr :: UnOp -> Doc #

pprPrec :: Int -> UnOp -> Doc #

pprList :: [UnOp] -> Doc #

data BinOp Source #

Binary operators. These correspond closely to the binary operators in LLVM. Most are parametrised by their expected input and output types.

Constructors

Add IntType Overflow

Integer addition.

FAdd FloatType

Floating-point addition.

Sub IntType Overflow

Integer subtraction.

FSub FloatType

Floating-point subtraction.

Mul IntType Overflow

Integer multiplication.

FMul FloatType

Floating-point multiplication.

UDiv IntType Safety

Unsigned integer division. Rounds towards negativity infinity. Note: this is different from LLVM.

UDivUp IntType Safety

Unsigned integer division. Rounds towards positive infinity.

SDiv IntType Safety

Signed integer division. Rounds towards negativity infinity. Note: this is different from LLVM.

SDivUp IntType Safety

Signed integer division. Rounds towards positive infinity.

FDiv FloatType

Floating-point division.

FMod FloatType

Floating-point modulus.

UMod IntType Safety

Unsigned integer modulus; the countepart to UDiv.

SMod IntType Safety

Signed integer modulus; the countepart to SDiv.

SQuot IntType Safety

Signed integer division. Rounds towards zero. This corresponds to the sdiv instruction in LLVM and integer division in C.

SRem IntType Safety

Signed integer division. Rounds towards zero. This corresponds to the srem instruction in LLVM and integer modulo in C.

SMin IntType

Returns the smallest of two signed integers.

UMin IntType

Returns the smallest of two unsigned integers.

FMin FloatType

Returns the smallest of two floating-point numbers.

SMax IntType

Returns the greatest of two signed integers.

UMax IntType

Returns the greatest of two unsigned integers.

FMax FloatType

Returns the greatest of two floating-point numbers.

Shl IntType

Left-shift.

LShr IntType

Logical right-shift, zero-extended.

AShr IntType

Arithmetic right-shift, sign-extended.

And IntType

Bitwise and.

Or IntType

Bitwise or.

Xor IntType

Bitwise exclusive-or.

Pow IntType

Integer exponentiation.

FPow FloatType

Floating-point exponentiation.

LogAnd

Boolean and - not short-circuiting.

LogOr

Boolean or - not short-circuiting.

Instances

Instances details
Eq BinOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

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

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

Ord BinOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

compare :: BinOp -> BinOp -> Ordering #

(<) :: BinOp -> BinOp -> Bool #

(<=) :: BinOp -> BinOp -> Bool #

(>) :: BinOp -> BinOp -> Bool #

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

max :: BinOp -> BinOp -> BinOp #

min :: BinOp -> BinOp -> BinOp #

Show BinOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

Pretty BinOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

ppr :: BinOp -> Doc #

pprPrec :: Int -> BinOp -> Doc #

pprList :: [BinOp] -> Doc #

data CmpOp Source #

Comparison operators are like BinOps, but they always return a boolean value. The somewhat ugly constructor names are straight out of LLVM.

Constructors

CmpEq PrimType

All types equality.

CmpUlt IntType

Unsigned less than.

CmpUle IntType

Unsigned less than or equal.

CmpSlt IntType

Signed less than.

CmpSle IntType

Signed less than or equal.

FCmpLt FloatType

Floating-point less than.

FCmpLe FloatType

Floating-point less than or equal.

CmpLlt

Boolean less than.

CmpLle

Boolean less than or equal.

Instances

Instances details
Eq CmpOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

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

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

Ord CmpOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

compare :: CmpOp -> CmpOp -> Ordering #

(<) :: CmpOp -> CmpOp -> Bool #

(<=) :: CmpOp -> CmpOp -> Bool #

(>) :: CmpOp -> CmpOp -> Bool #

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

max :: CmpOp -> CmpOp -> CmpOp #

min :: CmpOp -> CmpOp -> CmpOp #

Show CmpOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

showsPrec :: Int -> CmpOp -> ShowS #

show :: CmpOp -> String #

showList :: [CmpOp] -> ShowS #

Pretty CmpOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

ppr :: CmpOp -> Doc #

pprPrec :: Int -> CmpOp -> Doc #

pprList :: [CmpOp] -> Doc #

data ConvOp Source #

Conversion operators try to generalise the from t0 x to t1 instructions from LLVM.

Constructors

ZExt IntType IntType

Zero-extend the former integer type to the latter. If the new type is smaller, the result is a truncation.

SExt IntType IntType

Sign-extend the former integer type to the latter. If the new type is smaller, the result is a truncation.

FPConv FloatType FloatType

Convert value of the former floating-point type to the latter. If the new type is smaller, the result is a truncation.

FPToUI FloatType IntType

Convert a floating-point value to the nearest unsigned integer (rounding towards zero).

FPToSI FloatType IntType

Convert a floating-point value to the nearest signed integer (rounding towards zero).

UIToFP IntType FloatType

Convert an unsigned integer to a floating-point value.

SIToFP IntType FloatType

Convert a signed integer to a floating-point value.

IToB IntType

Convert an integer to a boolean value. Zero becomes false; anything else is true.

BToI IntType

Convert a boolean to an integer. True is converted to 1 and False to 0.

FToB FloatType

Convert a float to a boolean value. Zero becomes false; | anything else is true.

BToF FloatType

Convert a boolean to a float. True is converted to 1 and False to 0.

Instances

Instances details
Eq ConvOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

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

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

Ord ConvOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Show ConvOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Pretty ConvOp Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

ppr :: ConvOp -> Doc #

pprPrec :: Int -> ConvOp -> Doc #

pprList :: [ConvOp] -> Doc #

data OpaqueOp Source #

Apart from being Opaque, what else is going on here?

Constructors

OpaqueNil

No special operation.

OpaqueTrace String

Print the argument, prefixed by this string.

Instances

Instances details
Eq OpaqueOp Source # 
Instance details

Defined in Futhark.IR.Syntax

Ord OpaqueOp Source # 
Instance details

Defined in Futhark.IR.Syntax

Show OpaqueOp Source # 
Instance details

Defined in Futhark.IR.Syntax

data DimChange d Source #

The new dimension in a Reshape-like operation. This allows us to disambiguate "real" reshapes, that change the actual shape of the array, from type coercions that are just present to make the types work out. The two constructors are considered equal for purposes of Eq.

Constructors

DimCoercion d

The new dimension is guaranteed to be numerically equal to the old one.

DimNew d

The new dimension is not necessarily numerically equal to the old one.

Instances

Instances details
Functor DimChange Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

fmap :: (a -> b) -> DimChange a -> DimChange b #

(<$) :: a -> DimChange b -> DimChange a #

Foldable DimChange Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

fold :: Monoid m => DimChange m -> m #

foldMap :: Monoid m => (a -> m) -> DimChange a -> m #

foldMap' :: Monoid m => (a -> m) -> DimChange a -> m #

foldr :: (a -> b -> b) -> b -> DimChange a -> b #

foldr' :: (a -> b -> b) -> b -> DimChange a -> b #

foldl :: (b -> a -> b) -> b -> DimChange a -> b #

foldl' :: (b -> a -> b) -> b -> DimChange a -> b #

foldr1 :: (a -> a -> a) -> DimChange a -> a #

foldl1 :: (a -> a -> a) -> DimChange a -> a #

toList :: DimChange a -> [a] #

null :: DimChange a -> Bool #

length :: DimChange a -> Int #

elem :: Eq a => a -> DimChange a -> Bool #

maximum :: Ord a => DimChange a -> a #

minimum :: Ord a => DimChange a -> a #

sum :: Num a => DimChange a -> a #

product :: Num a => DimChange a -> a #

Traversable DimChange Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

traverse :: Applicative f => (a -> f b) -> DimChange a -> f (DimChange b) #

sequenceA :: Applicative f => DimChange (f a) -> f (DimChange a) #

mapM :: Monad m => (a -> m b) -> DimChange a -> m (DimChange b) #

sequence :: Monad m => DimChange (m a) -> m (DimChange a) #

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

Defined in Futhark.IR.Syntax

Methods

(==) :: DimChange d -> DimChange d -> Bool #

(/=) :: DimChange d -> DimChange d -> Bool #

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

Defined in Futhark.IR.Syntax

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

Defined in Futhark.IR.Syntax

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

Defined in Futhark.IR.Pretty

Methods

ppr :: DimChange d -> Doc #

pprPrec :: Int -> DimChange d -> Doc #

pprList :: [DimChange d] -> Doc #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: DimChange d -> FV Source #

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

Defined in Futhark.Transform.Substitute

type ShapeChange d = [DimChange d] Source #

A list of DimChanges, indicating the new dimensions of an array.

type WithAccInput rep = (Shape, [VName], Maybe (Lambda rep, [SubExp])) Source #

The input to a WithAcc construct. Comprises the index space of the accumulator, the underlying arrays, and possibly a combining function.

data Exp rep Source #

The root Futhark expression type. The Op constructor contains a rep-specific operation. Do-loops, branches and function calls are special. Everything else is a simple BasicOp.

Constructors

BasicOp BasicOp

A simple (non-recursive) operation.

Apply Name [(SubExp, Diet)] [RetType rep] (Safety, SrcLoc, [SrcLoc]) 
If SubExp (Body rep) (Body rep) (IfDec (BranchType rep)) 
DoLoop [(FParam rep, SubExp)] (LoopForm rep) (Body rep)

loop {a} = {v} (for i < n|while b) do b.

WithAcc [WithAccInput rep] (Lambda rep)

Create accumulators backed by the given arrays (which are consumed) and pass them to the lambda, which must return the updated accumulators and possibly some extra values. The accumulators are turned back into arrays. The Shape is the write index space. The corresponding arrays must all have this shape outermost. This construct is not part of BasicOp because we need the rep parameter.

Op (Op rep) 

Instances

Instances details
RepTypes rep => Eq (Exp rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: Exp rep -> Exp rep -> Bool #

(/=) :: Exp rep -> Exp rep -> Bool #

RepTypes rep => Ord (Exp rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Exp rep -> Exp rep -> Ordering #

(<) :: Exp rep -> Exp rep -> Bool #

(<=) :: Exp rep -> Exp rep -> Bool #

(>) :: Exp rep -> Exp rep -> Bool #

(>=) :: Exp rep -> Exp rep -> Bool #

max :: Exp rep -> Exp rep -> Exp rep #

min :: Exp rep -> Exp rep -> Exp rep #

RepTypes rep => Show (Exp rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> Exp rep -> ShowS #

show :: Exp rep -> String #

showList :: [Exp rep] -> ShowS #

PrettyRep rep => Pretty (Exp rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Exp rep -> Doc #

pprPrec :: Int -> Exp rep -> Doc #

pprList :: [Exp rep] -> Doc #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Exp rep -> FV Source #

Substitutable rep => Substitute (Exp rep) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Exp rep -> Exp rep Source #

Renameable rep => Rename (Exp rep) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Exp rep -> RenameM (Exp rep) Source #

data LoopForm rep Source #

For-loop or while-loop?

Instances

Instances details
Scoped rep (LoopForm rep) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: LoopForm rep -> Scope rep Source #

RepTypes rep => Eq (LoopForm rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: LoopForm rep -> LoopForm rep -> Bool #

(/=) :: LoopForm rep -> LoopForm rep -> Bool #

RepTypes rep => Ord (LoopForm rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: LoopForm rep -> LoopForm rep -> Ordering #

(<) :: LoopForm rep -> LoopForm rep -> Bool #

(<=) :: LoopForm rep -> LoopForm rep -> Bool #

(>) :: LoopForm rep -> LoopForm rep -> Bool #

(>=) :: LoopForm rep -> LoopForm rep -> Bool #

max :: LoopForm rep -> LoopForm rep -> LoopForm rep #

min :: LoopForm rep -> LoopForm rep -> LoopForm rep #

RepTypes rep => Show (LoopForm rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> LoopForm rep -> ShowS #

show :: LoopForm rep -> String #

showList :: [LoopForm rep] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: LoopForm rep -> FV Source #

data IfDec rt Source #

Data associated with a branch.

Constructors

IfDec 

Fields

Instances

Instances details
Eq rt => Eq (IfDec rt) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: IfDec rt -> IfDec rt -> Bool #

(/=) :: IfDec rt -> IfDec rt -> Bool #

Ord rt => Ord (IfDec rt) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: IfDec rt -> IfDec rt -> Ordering #

(<) :: IfDec rt -> IfDec rt -> Bool #

(<=) :: IfDec rt -> IfDec rt -> Bool #

(>) :: IfDec rt -> IfDec rt -> Bool #

(>=) :: IfDec rt -> IfDec rt -> Bool #

max :: IfDec rt -> IfDec rt -> IfDec rt #

min :: IfDec rt -> IfDec rt -> IfDec rt #

Show rt => Show (IfDec rt) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> IfDec rt -> ShowS #

show :: IfDec rt -> String #

showList :: [IfDec rt] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: IfDec a -> FV Source #

data IfSort Source #

What kind of branch is this? This has no semantic meaning, but provides hints to simplifications.

Constructors

IfNormal

An ordinary branch.

IfFallback

A branch where the "true" case is what we are actually interested in, and the "false" case is only present as a fallback for when the true case cannot be safely evaluated. The compiler is permitted to optimise away the branch if the true case contains only safe statements.

IfEquiv

Both of these branches are semantically equivalent, and it is fine to eliminate one if it turns out to have problems (e.g. contain things we cannot generate code for).

Instances

Instances details
Eq IfSort Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

Ord IfSort Source # 
Instance details

Defined in Futhark.IR.Syntax

Show IfSort Source # 
Instance details

Defined in Futhark.IR.Syntax

data Safety Source #

Whether something is safe or unsafe (mostly function calls, and in the context of whether operations are dynamically checked). When we inline an Unsafe function, we remove all safety checks in its body. The Ord instance picks Unsafe as being less than Safe.

For operations like integer division, a safe division will not explode the computer in case of division by zero, but instead return some unspecified value. This always involves a run-time check, so generally the unsafe variant is what the compiler will insert, but guarded by an explicit assertion elsewhere. Safe operations are useful when the optimiser wants to move e.g. a division to a location where the divisor may be zero, but where the result will only be used when it is non-zero (so it doesn't matter what result is provided with a zero divisor, as long as the program keeps running).

Constructors

Unsafe 
Safe 

Instances

Instances details
Eq Safety Source # 
Instance details

Defined in Futhark.IR.Primitive

Methods

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

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

Ord Safety Source # 
Instance details

Defined in Futhark.IR.Primitive

Show Safety Source # 
Instance details

Defined in Futhark.IR.Primitive

data Lambda rep Source #

Anonymous function for use in a SOAC.

Constructors

Lambda 

Fields

Instances

Instances details
Scoped rep (Lambda rep) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: Lambda rep -> Scope rep Source #

RepTypes rep => Eq (Lambda rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: Lambda rep -> Lambda rep -> Bool #

(/=) :: Lambda rep -> Lambda rep -> Bool #

RepTypes rep => Ord (Lambda rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Lambda rep -> Lambda rep -> Ordering #

(<) :: Lambda rep -> Lambda rep -> Bool #

(<=) :: Lambda rep -> Lambda rep -> Bool #

(>) :: Lambda rep -> Lambda rep -> Bool #

(>=) :: Lambda rep -> Lambda rep -> Bool #

max :: Lambda rep -> Lambda rep -> Lambda rep #

min :: Lambda rep -> Lambda rep -> Lambda rep #

RepTypes rep => Show (Lambda rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> Lambda rep -> ShowS #

show :: Lambda rep -> String #

showList :: [Lambda rep] -> ShowS #

PrettyRep rep => Pretty (Lambda rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Lambda rep -> Doc #

pprPrec :: Int -> Lambda rep -> Doc #

pprList :: [Lambda rep] -> Doc #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Lambda rep -> FV Source #

Substitutable rep => Substitute (Lambda rep) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Renameable rep => Rename (Lambda rep) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: Lambda rep -> RenameM (Lambda rep) Source #

Definitions

data Param dec Source #

A function or lambda parameter.

Constructors

Param 

Fields

Instances

Instances details
Functor Param Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

fmap :: (a -> b) -> Param a -> Param b #

(<$) :: a -> Param b -> Param a #

Foldable Param Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

fold :: Monoid m => Param m -> m #

foldMap :: Monoid m => (a -> m) -> Param a -> m #

foldMap' :: Monoid m => (a -> m) -> Param a -> m #

foldr :: (a -> b -> b) -> b -> Param a -> b #

foldr' :: (a -> b -> b) -> b -> Param a -> b #

foldl :: (b -> a -> b) -> b -> Param a -> b #

foldl' :: (b -> a -> b) -> b -> Param a -> b #

foldr1 :: (a -> a -> a) -> Param a -> a #

foldl1 :: (a -> a -> a) -> Param a -> a #

toList :: Param a -> [a] #

null :: Param a -> Bool #

length :: Param a -> Int #

elem :: Eq a => a -> Param a -> Bool #

maximum :: Ord a => Param a -> a #

minimum :: Ord a => Param a -> a #

sum :: Num a => Param a -> a #

product :: Num a => Param a -> a #

Traversable Param Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

traverse :: Applicative f => (a -> f b) -> Param a -> f (Param b) #

sequenceA :: Applicative f => Param (f a) -> f (Param a) #

mapM :: Monad m => (a -> m b) -> Param a -> m (Param b) #

sequence :: Monad m => Param (m a) -> m (Param a) #

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

Defined in Futhark.IR.Syntax.Core

Methods

(==) :: Param dec -> Param dec -> Bool #

(/=) :: Param dec -> Param dec -> Bool #

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

Defined in Futhark.IR.Syntax.Core

Methods

compare :: Param dec -> Param dec -> Ordering #

(<) :: Param dec -> Param dec -> Bool #

(<=) :: Param dec -> Param dec -> Bool #

(>) :: Param dec -> Param dec -> Bool #

(>=) :: Param dec -> Param dec -> Bool #

max :: Param dec -> Param dec -> Param dec #

min :: Param dec -> Param dec -> Param dec #

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

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Param dec -> ShowS #

show :: Param dec -> String #

showList :: [Param dec] -> ShowS #

Pretty t => Pretty (Param t) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Param t -> Doc #

pprPrec :: Int -> Param t -> Doc #

pprList :: [Param t] -> Doc #

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

Defined in Futhark.IR.Prop.Types

Methods

declTypeOf :: Param dec -> DeclType Source #

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

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Param dec -> Type Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Param dec -> FV Source #

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

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Param dec -> Param dec Source #

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

Defined in Futhark.Transform.Rename

Methods

rename :: Param dec -> RenameM (Param dec) Source #

type FParam rep = Param (FParamInfo rep) Source #

A function and loop parameter.

type LParam rep = Param (LParamInfo rep) Source #

A lambda parameter.

data FunDef rep Source #

Function Declarations

Constructors

FunDef 

Fields

Instances

Instances details
Scoped rep (FunDef rep) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: FunDef rep -> Scope rep Source #

RepTypes rep => Eq (FunDef rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: FunDef rep -> FunDef rep -> Bool #

(/=) :: FunDef rep -> FunDef rep -> Bool #

RepTypes rep => Ord (FunDef rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: FunDef rep -> FunDef rep -> Ordering #

(<) :: FunDef rep -> FunDef rep -> Bool #

(<=) :: FunDef rep -> FunDef rep -> Bool #

(>) :: FunDef rep -> FunDef rep -> Bool #

(>=) :: FunDef rep -> FunDef rep -> Bool #

max :: FunDef rep -> FunDef rep -> FunDef rep #

min :: FunDef rep -> FunDef rep -> FunDef rep #

RepTypes rep => Show (FunDef rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> FunDef rep -> ShowS #

show :: FunDef rep -> String #

showList :: [FunDef rep] -> ShowS #

PrettyRep rep => Pretty (FunDef rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: FunDef rep -> Doc #

pprPrec :: Int -> FunDef rep -> Doc #

pprList :: [FunDef rep] -> Doc #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: FunDef rep -> FV Source #

Renameable rep => Rename (FunDef rep) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: FunDef rep -> RenameM (FunDef rep) Source #

type EntryPoint = (Name, [EntryParam], [EntryPointType]) Source #

Information about the inputs and outputs (return value) of an entry point.

data EntryParam Source #

An entry point parameter, comprising its name and original type.

data EntryPointType Source #

Every entry point argument and return value has an annotation indicating how it maps to the original source program type.

Constructors

TypeUnsigned Uniqueness

Is an unsigned integer or array of unsigned integers.

TypeOpaque Uniqueness String Int

A black box type comprising this many core values. The string is a human-readable description with no other semantics.

TypeDirect Uniqueness

Maps directly.

data Prog rep Source #

An entire Futhark program.

Constructors

Prog 

Fields

  • progConsts :: Stms rep

    Top-level constants that are computed at program startup, and which are in scope inside all functions.

  • progFuns :: [FunDef rep]

    The functions comprising the program. All funtions are also available in scope in the definitions of the constants, so be careful not to introduce circular dependencies (not currently checked).

Instances

Instances details
RepTypes rep => Eq (Prog rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: Prog rep -> Prog rep -> Bool #

(/=) :: Prog rep -> Prog rep -> Bool #

RepTypes rep => Ord (Prog rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Prog rep -> Prog rep -> Ordering #

(<) :: Prog rep -> Prog rep -> Bool #

(<=) :: Prog rep -> Prog rep -> Bool #

(>) :: Prog rep -> Prog rep -> Bool #

(>=) :: Prog rep -> Prog rep -> Bool #

max :: Prog rep -> Prog rep -> Prog rep #

min :: Prog rep -> Prog rep -> Prog rep #

RepTypes rep => Show (Prog rep) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> Prog rep -> ShowS #

show :: Prog rep -> String #

showList :: [Prog rep] -> ShowS #

PrettyRep rep => Pretty (Prog rep) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Prog rep -> Doc #

pprPrec :: Int -> Prog rep -> Doc #

pprList :: [Prog rep] -> Doc #

Utils

oneStm :: Stm rep -> Stms rep Source #

A single statement.

stmsFromList :: [Stm rep] -> Stms rep Source #

Convert a statement list to a statement sequence.

stmsToList :: Stms rep -> [Stm rep] Source #

Convert a statement sequence to a statement list.

stmsHead :: Stms rep -> Maybe (Stm rep, Stms rep) Source #

The first statement in the sequence, if any.

subExpRes :: SubExp -> SubExpRes Source #

Construct a SubExpRes with no certificates.

subExpsRes :: [SubExp] -> Result Source #

Construct a Result from subexpressions.

varRes :: VName -> SubExpRes Source #

Construct a SubExpRes from a variable name.

varsRes :: [VName] -> Result Source #

Construct a Result from variable names.