futhark-0.19.4: 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 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 Pattern alongside an expression ExpT. A pattern contains a "context" part and a "value" part. The context is used for things like the size of arrays in the value part whose size is existential.

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}

Lores

Most AST types (Stm, ExpT, Prog, etc) are parameterised by a type parameter with the somewhat silly name lore. The lore specifies how to fill out various polymorphic parts of the AST. For example, ExpT has a constructor Op whose payload depends on lore, via the use of a type family called Op (a kind of type-level function) which is applied to the lore. The SOACS representation (Futhark.IR.SOACS) thus uses a lore 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 PatElemT) are also type families.

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

Essentially, the lore 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).

Defining a new representation (or lore) 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

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

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

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.

stripDims :: Int -> a -> a Source #

stripDims n shape strips the outer n dimensions from shape.

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

Methods

simplify :: SimplifiableLore lore => Space -> SimpleM lore Space Source #

data TypeBase shape u Source #

A Futhark type is either an array or an element type. When comparing types for equality with ==, shapes must match.

Constructors

Prim PrimType 
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 shape, Eq u) => 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 shape, Ord u) => 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 shape, Show u) => 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 :: SimplifiableLore lore => TypeBase shape u -> SimpleM lore (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 #

Attributes

data Attr Source #

A single attribute.

Constructors

AttrAtom Name 
AttrComp Name [Attr] 

Instances

Instances details
Eq Attr Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

Ord Attr Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Attr -> Attr -> Ordering #

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

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

(>) :: Attr -> Attr -> Bool #

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

max :: Attr -> Attr -> Attr #

min :: Attr -> Attr -> Attr #

Show Attr Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> Attr -> ShowS #

show :: Attr -> String #

showList :: [Attr] -> ShowS #

IsString Attr Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

fromString :: String -> Attr #

Pretty Attr Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Attr -> Doc #

pprPrec :: Int -> Attr -> Doc #

pprList :: [Attr] -> Doc #

newtype Attrs Source #

Every statement is associated with a set of attributes, which can have various effects throughout the compiler.

Constructors

Attrs 

Fields

Instances

Instances details
Eq Attrs Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

Ord Attrs Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Attrs -> Attrs -> Ordering #

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

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

(>) :: Attrs -> Attrs -> Bool #

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

max :: Attrs -> Attrs -> Attrs #

min :: Attrs -> Attrs -> Attrs #

Show Attrs Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> Attrs -> ShowS #

show :: Attrs -> String #

showList :: [Attrs] -> ShowS #

Semigroup Attrs Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(<>) :: Attrs -> Attrs -> Attrs #

sconcat :: NonEmpty Attrs -> Attrs #

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

Monoid Attrs Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

mempty :: Attrs #

mappend :: Attrs -> Attrs -> Attrs #

mconcat :: [Attrs] -> Attrs #

FreeIn Attrs Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Attrs -> FV Source #

Substitute Attrs Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename Attrs Source # 
Instance details

Defined in Futhark.Transform.Rename

oneAttr :: Attr -> Attrs Source #

Construct Attrs from a single Attr.

inAttrs :: Attr -> Attrs -> Bool Source #

Is the given attribute to be found in the attribute set?

withoutAttrs :: Attrs -> Attrs -> Attrs Source #

x withoutAttrs y gives x except for any attributes also in y.

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 :: MonadBinder m => SubExp -> m (Exp (Lore m)) Source #

Simplifiable SubExp Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Simplifiable ExtSize Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

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

type PatElem lore = PatElemT (LetDec lore) Source #

A type alias for namespace control.

data PatElemT 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 PatElemT Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Foldable PatElemT Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

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

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

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

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

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

toList :: PatElemT a -> [a] #

null :: PatElemT a -> Bool #

length :: PatElemT a -> Int #

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

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

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

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

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

Traversable PatElemT Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

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

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

Defined in Futhark.IR.Syntax.Core

Methods

compare :: PatElemT dec -> PatElemT dec -> Ordering #

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

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

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

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

max :: PatElemT dec -> PatElemT dec -> PatElemT dec #

min :: PatElemT dec -> PatElemT dec -> PatElemT dec #

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

Defined in Futhark.IR.Syntax.Core

Methods

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

show :: PatElemT dec -> String #

showList :: [PatElemT dec] -> ShowS #

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

Defined in Futhark.IR.Pretty

Methods

ppr :: PatElemT t -> Doc #

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

pprList :: [PatElemT t] -> Doc #

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

Defined in Futhark.IR.Prop.Types

Methods

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

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

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: PatElemT dec -> Type Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: PatElemT dec -> FV Source #

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

Defined in Futhark.Transform.Substitute

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

Defined in Futhark.Transform.Rename

Methods

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

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

Defined in Futhark.IR.Prop.Aliases

Methods

aliasesOf :: PatElemT dec -> Names Source #

data PatternT dec Source #

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

Constructors

Pattern 

Fields

Instances

Instances details
Functor PatternT Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

Foldable PatternT Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

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

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

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

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

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

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

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

toList :: PatternT a -> [a] #

null :: PatternT a -> Bool #

length :: PatternT a -> Int #

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

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

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

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

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

Traversable PatternT Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

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

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

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

Defined in Futhark.IR.Syntax

Methods

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

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

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

Defined in Futhark.IR.Syntax

Methods

compare :: PatternT dec -> PatternT dec -> Ordering #

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

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

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

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

max :: PatternT dec -> PatternT dec -> PatternT dec #

min :: PatternT dec -> PatternT dec -> PatternT dec #

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

Defined in Futhark.IR.Syntax

Methods

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

show :: PatternT dec -> String #

showList :: [PatternT dec] -> ShowS #

Semigroup (PatternT dec) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

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

Monoid (PatternT dec) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

mempty :: PatternT dec #

mappend :: PatternT dec -> PatternT dec -> PatternT dec #

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

Pretty (PatElemT dec) => Pretty (PatternT dec) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: PatternT dec -> Doc #

pprPrec :: Int -> PatternT dec -> Doc #

pprList :: [PatternT dec] -> Doc #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: PatternT dec -> FV Source #

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

Defined in Futhark.Transform.Substitute

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

Defined in Futhark.Transform.Rename

Methods

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

type Pattern lore = PatternT (LetDec lore) Source #

A type alias for namespace control.

data StmAux dec Source #

Auxilliary Information associated with a statement.

Constructors

StmAux 

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 lore Source #

A local variable binding.

Constructors

Let 

Fields

Instances

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

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: Stm lore -> Scope lore Source #

Scoped lore (Stms lore) Source # 
Instance details

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: Stms lore -> Scope lore Source #

Decorations lore => Eq (Stm lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

Decorations lore => Ord (Stm lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Stm lore -> Stm lore -> Ordering #

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

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

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

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

max :: Stm lore -> Stm lore -> Stm lore #

min :: Stm lore -> Stm lore -> Stm lore #

Decorations lore => Show (Stm lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

show :: Stm lore -> String #

showList :: [Stm lore] -> ShowS #

PrettyLore lore => Pretty (Stms lore) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Stms lore -> Doc #

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

pprList :: [Stms lore] -> Doc #

PrettyLore lore => Pretty (Stm lore) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Stm lore -> Doc #

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

pprList :: [Stm lore] -> Doc #

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 #

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

Defined in Futhark.Transform.Substitute

Methods

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

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

Defined in Futhark.Transform.Substitute

Methods

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

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

Defined in Futhark.Transform.Rename

Methods

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

type Stms lore = Seq (Stm lore) Source #

A sequence of statements.

type Result = [SubExp] Source #

The result of a body is a sequence of subexpressions.

data BodyT lore Source #

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

Constructors

Body 

Fields

Instances

Instances details
Decorations lore => Eq (BodyT lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: BodyT lore -> BodyT lore -> Bool #

(/=) :: BodyT lore -> BodyT lore -> Bool #

Decorations lore => Ord (BodyT lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: BodyT lore -> BodyT lore -> Ordering #

(<) :: BodyT lore -> BodyT lore -> Bool #

(<=) :: BodyT lore -> BodyT lore -> Bool #

(>) :: BodyT lore -> BodyT lore -> Bool #

(>=) :: BodyT lore -> BodyT lore -> Bool #

max :: BodyT lore -> BodyT lore -> BodyT lore #

min :: BodyT lore -> BodyT lore -> BodyT lore #

Decorations lore => Show (BodyT lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> BodyT lore -> ShowS #

show :: BodyT lore -> String #

showList :: [BodyT lore] -> ShowS #

PrettyLore lore => Pretty (Body lore) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Body lore -> Doc #

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

pprList :: [Body lore] -> Doc #

(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 #

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

Defined in Futhark.Transform.Substitute

Methods

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

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

Defined in Futhark.Transform.Rename

Methods

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

type Body = BodyT Source #

Type alias for namespace reasons.

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 SubExp

Semantically and operationally just identity, but is invisible/impenetrable to optimisations (hopefully). This is just a hack to avoid optimisation (so, to work around compiler limitations).

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 VName (Slice SubExp) SubExp

An in-place update of the given array at the given position. Consumes the array.

Concat Int VName [VName] SubExp

concat0([1],[2, 3, 4]) = [1, 2, 3, 4]@.

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.

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.

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 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.

data ExpT lore Source #

The root Futhark expression type. The Op constructor contains a lore-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 lore] (Safety, SrcLoc, [SrcLoc]) 
If SubExp (BodyT lore) (BodyT lore) (IfDec (BranchType lore)) 
DoLoop [(FParam lore, SubExp)] [(FParam lore, SubExp)] (LoopForm lore) (BodyT lore)

loop {a} = {v} (for i < n|while b) do b. The merge parameters are divided into context and value part.

Op (Op lore) 

Instances

Instances details
Decorations lore => Eq (ExpT lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: ExpT lore -> ExpT lore -> Bool #

(/=) :: ExpT lore -> ExpT lore -> Bool #

Decorations lore => Ord (ExpT lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: ExpT lore -> ExpT lore -> Ordering #

(<) :: ExpT lore -> ExpT lore -> Bool #

(<=) :: ExpT lore -> ExpT lore -> Bool #

(>) :: ExpT lore -> ExpT lore -> Bool #

(>=) :: ExpT lore -> ExpT lore -> Bool #

max :: ExpT lore -> ExpT lore -> ExpT lore #

min :: ExpT lore -> ExpT lore -> ExpT lore #

Decorations lore => Show (ExpT lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> ExpT lore -> ShowS #

show :: ExpT lore -> String #

showList :: [ExpT lore] -> ShowS #

PrettyLore lore => Pretty (Exp lore) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Exp lore -> Doc #

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

pprList :: [Exp lore] -> Doc #

(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 #

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

Defined in Futhark.Transform.Substitute

Methods

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

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

Defined in Futhark.Transform.Rename

Methods

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

type Exp = ExpT Source #

A type alias for namespace control.

data LoopForm lore Source #

For-loop or while-loop?

Instances

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

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: LoopForm lore -> Scope lore Source #

Decorations lore => Eq (LoopForm lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

Decorations lore => Ord (LoopForm lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: LoopForm lore -> LoopForm lore -> Ordering #

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

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

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

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

max :: LoopForm lore -> LoopForm lore -> LoopForm lore #

min :: LoopForm lore -> LoopForm lore -> LoopForm lore #

Decorations lore => Show (LoopForm lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

show :: LoopForm lore -> String #

showList :: [LoopForm lore] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: LoopForm lore -> 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 LambdaT lore Source #

Anonymous function for use in a SOAC.

Constructors

Lambda 

Fields

Instances

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

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: Lambda lore -> Scope lore Source #

Decorations lore => Eq (LambdaT lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

(==) :: LambdaT lore -> LambdaT lore -> Bool #

(/=) :: LambdaT lore -> LambdaT lore -> Bool #

Decorations lore => Ord (LambdaT lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: LambdaT lore -> LambdaT lore -> Ordering #

(<) :: LambdaT lore -> LambdaT lore -> Bool #

(<=) :: LambdaT lore -> LambdaT lore -> Bool #

(>) :: LambdaT lore -> LambdaT lore -> Bool #

(>=) :: LambdaT lore -> LambdaT lore -> Bool #

max :: LambdaT lore -> LambdaT lore -> LambdaT lore #

min :: LambdaT lore -> LambdaT lore -> LambdaT lore #

Decorations lore => Show (LambdaT lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

showsPrec :: Int -> LambdaT lore -> ShowS #

show :: LambdaT lore -> String #

showList :: [LambdaT lore] -> ShowS #

PrettyLore lore => Pretty (Lambda lore) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Lambda lore -> Doc #

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

pprList :: [Lambda lore] -> Doc #

(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 #

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

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> Lambda lore -> Lambda lore Source #

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

Defined in Futhark.Transform.Rename

Methods

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

type Lambda = LambdaT Source #

Type alias for namespacing reasons.

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 lore = Param (FParamInfo lore) Source #

A function and loop parameter.

type LParam lore = Param (LParamInfo lore) Source #

A lambda parameter.

data FunDef lore Source #

Function Declarations

Constructors

FunDef 

Fields

Instances

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

Defined in Futhark.IR.Prop.Scope

Methods

scopeOf :: FunDef lore -> Scope lore Source #

Decorations lore => Eq (FunDef lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

Decorations lore => Ord (FunDef lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: FunDef lore -> FunDef lore -> Ordering #

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

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

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

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

max :: FunDef lore -> FunDef lore -> FunDef lore #

min :: FunDef lore -> FunDef lore -> FunDef lore #

Decorations lore => Show (FunDef lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

show :: FunDef lore -> String #

showList :: [FunDef lore] -> ShowS #

PrettyLore lore => Pretty (FunDef lore) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: FunDef lore -> Doc #

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

pprList :: [FunDef lore] -> Doc #

(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 #

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

Defined in Futhark.Transform.Rename

Methods

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

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

Information about the parameters and return value of an entry point. The first element is for parameters, the second for return value.

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

Is an unsigned integer or array of unsigned integers.

TypeOpaque String Int

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

TypeDirect

Maps directly.

data Prog lore Source #

An entire Futhark program.

Constructors

Prog 

Fields

  • progConsts :: Stms lore

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

  • progFuns :: [FunDef lore]

    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
Decorations lore => Eq (Prog lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

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

Decorations lore => Ord (Prog lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

compare :: Prog lore -> Prog lore -> Ordering #

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

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

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

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

max :: Prog lore -> Prog lore -> Prog lore #

min :: Prog lore -> Prog lore -> Prog lore #

Decorations lore => Show (Prog lore) Source # 
Instance details

Defined in Futhark.IR.Syntax

Methods

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

show :: Prog lore -> String #

showList :: [Prog lore] -> ShowS #

PrettyLore lore => Pretty (Prog lore) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

ppr :: Prog lore -> Doc #

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

pprList :: [Prog lore] -> Doc #

Utils

oneStm :: Stm lore -> Stms lore Source #

A single statement.

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

Convert a statement list to a statement sequence.

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

Convert a statement sequence to a statement list.

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

The first statement in the sequence, if any.