futhark-0.22.2: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Futhark.IR.Syntax.Core

Description

The most primitive ("core") aspects of the AST. Split out of Futhark.IR.Syntax in order for Futhark.IR.Rep to use these definitions. This module is re-exported from Futhark.IR.Syntax and there should be no reason to include it explicitly.

Synopsis

Documentation

Types

data Commutativity Source #

Whether some operator is commutative or not. The Monoid instance returns the least commutative of its arguments.

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
Monoid Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Semigroup Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Show 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 FunReturns Source # 
Instance details

Defined in Futhark.IR.Mem

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.IR.RetType

Eq Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Ord Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Pretty Uniqueness Source # 
Instance details

Defined in Language.Futhark.Core

Methods

pretty :: Uniqueness -> Doc ann #

prettyList :: [Uniqueness] -> Doc ann #

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => [FunReturns] -> SimpleM rep [FunReturns] Source #

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
Monoid NoUniqueness Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Semigroup NoUniqueness Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Show NoUniqueness Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

HasLetDecMem LetDecMem Source # 
Instance details

Defined in Futhark.IR.Mem

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

SetType Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

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

Typed Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Type -> Type Source #

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.IR.Mem

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.IR.RetType

Eq NoUniqueness Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Ord NoUniqueness Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Pretty NoUniqueness Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: NoUniqueness -> Doc ann #

prettyList :: [NoUniqueness] -> Doc ann #

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 ShapeBase d Source #

The size of an array type as a list of its dimension sizes, with the type of sizes being parametric.

Constructors

Shape 

Fields

Instances

Instances details
Foldable ShapeBase Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

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

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

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

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

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

toList :: ShapeBase a -> [a] #

null :: ShapeBase a -> Bool #

length :: ShapeBase a -> Int #

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

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

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

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

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

Traversable ShapeBase Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

Functor ShapeBase Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

SetType Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

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

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 #

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.IR.RetType

Pretty ExtShape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: ExtShape -> Doc ann #

prettyList :: [ExtShape] -> Doc ann #

Pretty Shape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Shape -> Doc ann #

prettyList :: [Shape] -> Doc ann #

Monoid (ShapeBase d) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Semigroup (ShapeBase d) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

(<>) :: ShapeBase d -> ShapeBase d -> ShapeBase d #

sconcat :: NonEmpty (ShapeBase d) -> ShapeBase d #

stimes :: Integral b => b -> ShapeBase d -> ShapeBase d #

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

Defined in Futhark.IR.Syntax.Core

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: ShapeBase d -> FV Source #

FixExt d => FixExt (ShapeBase d) Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

fixExt :: Int -> SubExp -> ShapeBase d -> ShapeBase d Source #

ArrayShape (ShapeBase ExtSize) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

ArrayShape (ShapeBase SubExp) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Simplifiable d => Simplifiable (ShapeBase d) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => ShapeBase d -> SimpleM rep (ShapeBase d) Source #

Rename d => Rename (ShapeBase d) Source # 
Instance details

Defined in Futhark.Transform.Rename

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

Defined in Futhark.Transform.Substitute

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

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

Defined in Futhark.IR.Syntax.Core

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase ExtShape u -> Doc ann #

prettyList :: [TypeBase ExtShape u] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase Shape u -> Doc ann #

prettyList :: [TypeBase Shape u] -> Doc ann #

type Shape = ShapeBase SubExp Source #

The size of an array as a list of subexpressions. If a variable, that variable must be in scope where this array is used.

stripDims :: Int -> ShapeBase d -> ShapeBase d Source #

stripDims n shape strips the outer n dimensions from shape.

data Ext a Source #

Something that may be existential.

Constructors

Ext Int 
Free a 

Instances

Instances details
Foldable Ext Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

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

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

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

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

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

toList :: Ext a -> [a] #

null :: Ext a -> Bool #

length :: Ext a -> Int #

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

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

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

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

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

Traversable Ext Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

Functor Ext Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

FixExt ExtSize Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

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

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.IR.Mem

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.IR.Mem

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.IR.RetType

Simplifiable ExtSize Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => ExtSize -> SimpleM rep ExtSize Source #

Rename ExtSize Source # 
Instance details

Defined in Futhark.Transform.Rename

Pretty ExtShape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: ExtShape -> Doc ann #

prettyList :: [ExtShape] -> Doc ann #

Show a => Show (Ext a) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Ext a -> ShowS #

show :: Ext a -> String #

showList :: [Ext a] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Ext d -> FV Source #

ArrayShape (ShapeBase ExtSize) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => [FunReturns] -> SimpleM rep [FunReturns] Source #

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

Defined in Futhark.Transform.Substitute

Eq a => Eq (Ext a) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

(==) :: Ext a -> Ext a -> Bool #

(/=) :: Ext a -> Ext a -> Bool #

Ord a => Ord (Ext a) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

compare :: Ext a -> Ext a -> Ordering #

(<) :: Ext a -> Ext a -> Bool #

(<=) :: Ext a -> Ext a -> Bool #

(>) :: Ext a -> Ext a -> Bool #

(>=) :: Ext a -> Ext a -> Bool #

max :: Ext a -> Ext a -> Ext a #

min :: Ext a -> Ext a -> Ext a #

Pretty a => Pretty (Ext a) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Ext a -> Doc ann #

prettyList :: [Ext a] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase ExtShape u -> Doc ann #

prettyList :: [TypeBase ExtShape u] -> Doc ann #

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

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 #

type ExtSize = Ext SubExp Source #

The size of this dimension.

type ExtShape = ShapeBase ExtSize Source #

Like Shape but some of its elements may be bound in a local environment instead. These are denoted with integral indices.

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
Monoid Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

mempty :: Rank #

mappend :: Rank -> Rank -> Rank #

mconcat :: [Rank] -> Rank #

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 #

Show Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Rank -> ShowS #

show :: Rank -> String #

showList :: [Rank] -> ShowS #

ArrayShape Rank Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Rename Rank Source # 
Instance details

Defined in Futhark.Transform.Rename

Substitute Rank Source # 
Instance details

Defined in Futhark.Transform.Substitute

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 #

Pretty Rank Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Rank -> Doc ann #

prettyList :: [Rank] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase Rank u -> Doc ann #

prettyList :: [TypeBase Rank u] -> Doc ann #

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
Show Space Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Space -> ShowS #

show :: Space -> String #

showList :: [Space] -> ShowS #

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 :: forall {k} (rep :: k). SimplifiableRep rep => Space -> SimpleM rep Space Source #

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 #

Pretty Space Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Space -> Doc ann #

prettyList :: [Space] -> Doc ann #

type SpaceId = String Source #

A string representing a specific non-default memory space.

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

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

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

SetType Type Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

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

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 #

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.IR.RetType

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

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

Defined in Futhark.IR.Prop.Names

Methods

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

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

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

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => TypeBase shape u -> SimpleM rep (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 #

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 #

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

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase ExtShape u -> Doc ann #

prettyList :: [TypeBase ExtShape u] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase Rank u -> Doc ann #

prettyList :: [TypeBase Rank u] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase Shape u -> Doc ann #

prettyList :: [TypeBase Shape u] -> Doc ann #

type Type = TypeBase Shape NoUniqueness Source #

A type with shape information, used for describing the type of variables.

type ExtType = TypeBase ExtShape NoUniqueness Source #

A type with existentially quantified shapes - used as part of function (and function-like) return types. Generally only makes sense when used in a list.

type DeclType = TypeBase Shape Uniqueness Source #

A type with shape and uniqueness information, used declaring return- and parameters types.

type DeclExtType = TypeBase ExtShape Uniqueness Source #

An ExtType with uniqueness information, used for function return types.

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
Show Diet Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Diet -> ShowS #

show :: Diet -> String #

showList :: [Diet] -> ShowS #

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 #

newtype ErrorMsg a Source #

An error message is a list of error parts, which are concatenated to form the final message.

Constructors

ErrorMsg [ErrorMsgPart a] 

Instances

Instances details
Foldable ErrorMsg Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

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

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

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

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

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

toList :: ErrorMsg a -> [a] #

null :: ErrorMsg a -> Bool #

length :: ErrorMsg a -> Int #

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

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

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

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

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

Traversable ErrorMsg Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

Functor ErrorMsg Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

IsString (ErrorMsg a) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

fromString :: String -> ErrorMsg a #

Show a => Show (ErrorMsg a) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> ErrorMsg a -> ShowS #

show :: ErrorMsg a -> String #

showList :: [ErrorMsg a] -> ShowS #

Eq a => Eq (ErrorMsg a) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

(==) :: ErrorMsg a -> ErrorMsg a -> Bool #

(/=) :: ErrorMsg a -> ErrorMsg a -> Bool #

Ord a => Ord (ErrorMsg a) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

compare :: ErrorMsg a -> ErrorMsg a -> Ordering #

(<) :: ErrorMsg a -> ErrorMsg a -> Bool #

(<=) :: ErrorMsg a -> ErrorMsg a -> Bool #

(>) :: ErrorMsg a -> ErrorMsg a -> Bool #

(>=) :: ErrorMsg a -> ErrorMsg a -> Bool #

max :: ErrorMsg a -> ErrorMsg a -> ErrorMsg a #

min :: ErrorMsg a -> ErrorMsg a -> ErrorMsg a #

Pretty a => Pretty (ErrorMsg a) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: ErrorMsg a -> Doc ann #

prettyList :: [ErrorMsg a] -> Doc ann #

data ErrorMsgPart a Source #

A part of an error message.

Constructors

ErrorString Text

A literal string.

ErrorVal PrimType a

A run-time value.

Instances

Instances details
Foldable ErrorMsgPart Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

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

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

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

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

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

toList :: ErrorMsgPart a -> [a] #

null :: ErrorMsgPart a -> Bool #

length :: ErrorMsgPart a -> Int #

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

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

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

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

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

Traversable ErrorMsgPart Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

Functor ErrorMsgPart Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

IsString (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Show a => Show (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Eq a => Eq (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Ord a => Ord (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

errorMsgArgTypes :: ErrorMsg a -> [PrimType] Source #

How many non-constant parts does the error message have, and what is their type?

Entry point information

data ValueType Source #

An actual non-opaque type that can be passed to and from Futhark programs, or serve as the contents of opaque types. Scalars are represented with zero rank.

Instances

Instances details
Show ValueType Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Eq ValueType Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Ord ValueType Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Pretty ValueType Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: ValueType -> Doc ann #

prettyList :: [ValueType] -> Doc ann #

data OpaqueType Source #

The representation of an opaque type.

Constructors

OpaqueType [ValueType] 
OpaqueRecord [(Name, EntryPointType)]

Note that the field ordering here denote the actual representation - make sure it is preserved.

newtype OpaqueTypes Source #

Names of opaque types and their representation.

Constructors

OpaqueTypes [(String, OpaqueType)] 

data Signedness Source #

Since the core language does not care for signedness, but the source language does, entry point input/output information has metadata for integer types (and arrays containing these) that indicate whether they are really unsigned integers. This doesn't matter for non-integer types.

Constructors

Unsigned 
Signed 

data EntryPointType Source #

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

Constructors

TypeOpaque String

An opaque type of this name.

TypeTransparent ValueType

A transparent type, which is scalar if the rank is zero.

Attributes

data Attr Source #

A single attribute.

Instances

Instances details
IsString Attr Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

fromString :: String -> Attr #

Show Attr Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Attr -> ShowS #

show :: Attr -> String #

showList :: [Attr] -> ShowS #

Eq Attr Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord Attr Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

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 #

Pretty Attr Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Attr -> Doc ann #

prettyList :: [Attr] -> Doc ann #

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
Monoid Attrs Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

mempty :: Attrs #

mappend :: Attrs -> Attrs -> Attrs #

mconcat :: [Attrs] -> Attrs #

Semigroup Attrs Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

sconcat :: NonEmpty Attrs -> Attrs #

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

Show Attrs Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Attrs -> ShowS #

show :: Attrs -> String #

showList :: [Attrs] -> ShowS #

FreeIn Attrs Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Attrs -> FV Source #

Rename Attrs Source # 
Instance details

Defined in Futhark.Transform.Rename

Substitute Attrs Source # 
Instance details

Defined in Futhark.Transform.Substitute

Eq Attrs Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord Attrs Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

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 #

Pretty Attrs Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Attrs -> Doc ann #

prettyList :: [Attrs] -> Doc ann #

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.

mapAttrs :: (Attr -> a) -> Attrs -> [a] Source #

Map a function over an attribute set.

Values

data PrimValue Source #

Non-array values.

Constructors

IntValue !IntValue 
FloatValue !FloatValue 
BoolValue !Bool 
UnitValue

The only value of type Unit.

Instances

Instances details
Show PrimValue Source # 
Instance details

Defined in Language.Futhark.Primitive

IsValue PrimValue Source # 
Instance details

Defined in Futhark.IR.Prop.Constants

Eq PrimValue Source # 
Instance details

Defined in Language.Futhark.Primitive

Ord PrimValue Source # 
Instance details

Defined in Language.Futhark.Primitive

ToExp PrimValue Source # 
Instance details

Defined in Futhark.CodeGen.Backends.SimpleRep

Methods

toExp :: PrimValue -> SrcLoc -> Exp #

Pretty PrimValue Source # 
Instance details

Defined in Language.Futhark.Primitive

Methods

pretty :: PrimValue -> Doc ann #

prettyList :: [PrimValue] -> Doc ann #

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
Show Ident Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

FreeIn Ident Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Ident -> FV Source #

Typed Ident Source # 
Instance details

Defined in Futhark.IR.Prop.Types

Methods

typeOf :: Ident -> Type Source #

Rename Ident Source # 
Instance details

Defined in Futhark.Transform.Rename

Substitute Ident Source # 
Instance details

Defined in Futhark.Transform.Substitute

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 #

Pretty Ident Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Ident -> Doc ann #

prettyList :: [Ident] -> Doc ann #

newtype Certs Source #

A list of names used for certificates in some expressions.

Constructors

Certs 

Fields

Instances

Instances details
Monoid Certs Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

mempty :: Certs #

mappend :: Certs -> Certs -> Certs #

mconcat :: [Certs] -> Certs #

Semigroup Certs Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

(<>) :: Certs -> Certs -> Certs #

sconcat :: NonEmpty Certs -> Certs #

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

Show Certs Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Certs -> ShowS #

show :: Certs -> String #

showList :: [Certs] -> ShowS #

FreeIn Certs Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Certs -> FV Source #

Simplifiable Certs Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => Certs -> SimpleM rep Certs Source #

Rename Certs Source # 
Instance details

Defined in Futhark.Transform.Rename

Substitute Certs Source # 
Instance details

Defined in Futhark.Transform.Substitute

Eq Certs Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

Ord Certs Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

compare :: Certs -> Certs -> Ordering #

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

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

(>) :: Certs -> Certs -> Bool #

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

max :: Certs -> Certs -> Certs #

min :: Certs -> Certs -> Certs #

Pretty Certs Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Certs -> Doc ann #

prettyList :: [Certs] -> Doc ann #

MonadState (VNameSource, Bool, Certs) (SimpleM rep) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

get :: SimpleM rep (VNameSource, Bool, Certs) #

put :: (VNameSource, Bool, Certs) -> SimpleM rep () #

state :: ((VNameSource, Bool, Certs) -> (a, (VNameSource, Bool, Certs))) -> SimpleM rep a #

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
Show SubExp Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

ToExp SubExp Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

Methods

toExp :: forall {k} (rep :: k) r op. SubExp -> ImpM rep r op Exp Source #

toExp' :: PrimType -> SubExp -> Exp Source #

ToExp SubExp Source # 
Instance details

Defined in Futhark.Construct

Methods

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

HasLetDecMem LetDecMem Source # 
Instance details

Defined in Futhark.IR.Mem

FreeIn SubExp Source # 
Instance details

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: SubExp -> FV Source #

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.IR.Prop.Types

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 #

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 #

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.IR.Mem

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.IR.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.IR.Mem

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.IR.RetType

Simplifiable ExtSize Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => ExtSize -> SimpleM rep ExtSize Source #

Simplifiable SubExp Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => SubExp -> SimpleM rep SubExp Source #

Rename ExtSize Source # 
Instance details

Defined in Futhark.Transform.Rename

Rename SubExp Source # 
Instance details

Defined in Futhark.Transform.Rename

Substitute SubExp Source # 
Instance details

Defined in Futhark.Transform.Substitute

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

ToExp SubExp Source # 
Instance details

Defined in Futhark.CodeGen.Backends.SimpleRep

Methods

toExp :: SubExp -> SrcLoc -> Exp #

Pretty ExtShape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: ExtShape -> Doc ann #

prettyList :: [ExtShape] -> Doc ann #

Pretty Shape Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Shape -> Doc ann #

prettyList :: [Shape] -> Doc ann #

Pretty SubExp Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: SubExp -> Doc ann #

prettyList :: [SubExp] -> Doc ann #

ArrayShape (ShapeBase ExtSize) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

ArrayShape (ShapeBase SubExp) Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.IR.Mem

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => [FunReturns] -> SimpleM rep [FunReturns] Source #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase ExtShape u -> Doc ann #

prettyList :: [TypeBase ExtShape u] -> Doc ann #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: TypeBase Shape u -> Doc ann #

prettyList :: [TypeBase Shape u] -> Doc ann #

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

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

Defined in Futhark.IR.Mem

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 #

Typed (MemInfo SubExp NoUniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.IR.Mem

data Param dec Source #

A function or lambda parameter.

Constructors

Param 

Fields

Instances

Instances details
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) #

Functor Param Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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 #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Param dec -> FV Source #

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 #

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

Defined in Futhark.Transform.Rename

Methods

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

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

Defined in Futhark.Transform.Substitute

Methods

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

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 #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: Param t -> Doc ann #

prettyList :: [Param t] -> Doc ann #

data DimIndex d Source #

How to index a single dimension of an array.

Constructors

DimFix d

Fix index in this dimension.

DimSlice d d d

DimSlice start_offset num_elems stride.

Instances

Instances details
Foldable DimIndex Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

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

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

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

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

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

toList :: DimIndex a -> [a] #

null :: DimIndex a -> Bool #

length :: DimIndex a -> Int #

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

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

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

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

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

Traversable DimIndex Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

Functor DimIndex Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> DimIndex d -> ShowS #

show :: DimIndex d -> String #

showList :: [DimIndex d] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: DimIndex d -> FV Source #

Simplifiable d => Simplifiable (DimIndex d) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => DimIndex d -> SimpleM rep (DimIndex d) Source #

Rename d => Rename (DimIndex d) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: DimIndex d -> RenameM (DimIndex d) Source #

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

Defined in Futhark.Transform.Substitute

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

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

Defined in Futhark.IR.Syntax.Core

Methods

compare :: DimIndex d -> DimIndex d -> Ordering #

(<) :: DimIndex d -> DimIndex d -> Bool #

(<=) :: DimIndex d -> DimIndex d -> Bool #

(>) :: DimIndex d -> DimIndex d -> Bool #

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

max :: DimIndex d -> DimIndex d -> DimIndex d #

min :: DimIndex d -> DimIndex d -> DimIndex d #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: DimIndex d -> Doc ann #

prettyList :: [DimIndex d] -> Doc ann #

newtype Slice d Source #

A list of DimIndexs, indicating how an array should be sliced. Whenever a function accepts a Slice, that slice should be total, i.e, cover all dimensions of the array. Deviators should be indicated by taking a list of DimIndexes instead.

Constructors

Slice 

Fields

Instances

Instances details
Foldable Slice Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

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

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

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

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

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

toList :: Slice a -> [a] #

null :: Slice a -> Bool #

length :: Slice a -> Int #

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

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

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

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

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

Traversable Slice Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

Functor Slice Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

Defined in Futhark.IR.Syntax.Core

Methods

showsPrec :: Int -> Slice d -> ShowS #

show :: Slice d -> String #

showList :: [Slice d] -> ShowS #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: Slice d -> FV Source #

Simplifiable d => Simplifiable (Slice d) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: forall {k} (rep :: k). SimplifiableRep rep => Slice d -> SimpleM rep (Slice d) Source #

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

Defined in Futhark.Transform.Substitute

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

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

Defined in Futhark.IR.Syntax.Core

Methods

compare :: Slice d -> Slice d -> Ordering #

(<) :: Slice d -> Slice d -> Bool #

(<=) :: Slice d -> Slice d -> Bool #

(>) :: Slice d -> Slice d -> Bool #

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

max :: Slice d -> Slice d -> Slice d #

min :: Slice d -> Slice d -> Slice d #

Pretty a => Pretty (Slice a) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: Slice a -> Doc ann #

prettyList :: [Slice a] -> Doc ann #

dimFix :: DimIndex d -> Maybe d Source #

If the argument is a DimFix, return its component.

sliceIndices :: Slice d -> Maybe [d] Source #

If the slice is all DimFixs, return the components.

sliceDims :: Slice d -> [d] Source #

The dimensions of the array produced by this slice.

unitSlice :: Num d => d -> d -> DimIndex d Source #

A slice with a stride of one.

fixSlice :: Num d => Slice d -> [d] -> [d] Source #

Fix the DimSlices of a slice. The number of indexes must equal the length of sliceDims for the slice.

sliceSlice :: Num d => Slice d -> Slice d -> Slice d Source #

Further slice the DimSlices of a slice. The number of slices must equal the length of sliceDims for the slice.

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

Functor PatElem Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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 #

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

Defined in Futhark.IR.Prop.Aliases

Methods

aliasesOf :: PatElem dec -> Names Source #

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: PatElem dec -> FV Source #

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 #

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

Defined in Futhark.Transform.Rename

Methods

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

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

Defined in Futhark.Transform.Substitute

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 #

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

Defined in Futhark.IR.Pretty

Methods

pretty :: PatElem t -> Doc ann #

prettyList :: [PatElem t] -> Doc ann #

Flat (LMAD) slices

data FlatSlice d Source #

A flat slice is a way of viewing a one-dimensional array as a multi-dimensional array, using a more compressed mechanism than reshaping and using Slice. The initial d is an offset, and the list then specifies the shape of the resulting array.

Constructors

FlatSlice d [FlatDimIndex d] 

Instances

Instances details
Foldable FlatSlice Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

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

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

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

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

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

toList :: FlatSlice a -> [a] #

null :: FlatSlice a -> Bool #

length :: FlatSlice a -> Int #

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

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

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

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

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

Traversable FlatSlice Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

Functor FlatSlice Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

Defined in Futhark.IR.Syntax.Core

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: FlatSlice d -> FV Source #

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

Defined in Futhark.Transform.Substitute

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

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

Defined in Futhark.IR.Syntax.Core

Pretty a => Pretty (FlatSlice a) Source # 
Instance details

Defined in Futhark.IR.Pretty

Methods

pretty :: FlatSlice a -> Doc ann #

prettyList :: [FlatSlice a] -> Doc ann #

data FlatDimIndex d Source #

A dimension in a FlatSlice.

Constructors

FlatDimIndex 

Fields

  • d

    Number of elements in dimension

  • d

    Stride of dimension

Instances

Instances details
Foldable FlatDimIndex Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

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

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

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

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

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

toList :: FlatDimIndex a -> [a] #

null :: FlatDimIndex a -> Bool #

length :: FlatDimIndex a -> Int #

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

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

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

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

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

Traversable FlatDimIndex Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

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

Functor FlatDimIndex Source # 
Instance details

Defined in Futhark.IR.Syntax.Core

Methods

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

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

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

Defined in Futhark.IR.Syntax.Core

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

Defined in Futhark.IR.Prop.Names

Methods

freeIn' :: FlatDimIndex d -> FV Source #

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

Defined in Futhark.Transform.Substitute

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

Defined in Futhark.IR.Syntax.Core

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

Defined in Futhark.IR.Syntax.Core

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

Defined in Futhark.IR.Pretty

Methods

pretty :: FlatDimIndex d -> Doc ann #

prettyList :: [FlatDimIndex d] -> Doc ann #

flatSliceDims :: FlatSlice d -> [d] Source #

The dimensions (shape) of the view produced by a flat slice.

flatSliceStrides :: FlatSlice d -> [d] Source #

The strides of each dimension produced by a flat slice.