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

Safe HaskellNone
LanguageHaskell2010

Futhark.Representation.AST.Syntax.Core

Contents

Description

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

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
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.Representation.AST.Attributes.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: DeclType -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (Param (MemInfo SubExp Uniqueness ret)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (ParamT DeclType) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

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

Defined in Futhark.Representation.ExplicitMemory

DeclTyped (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

data NoUniqueness Source #

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

Constructors

NoUniqueness 
Instances
Eq NoUniqueness Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Ord NoUniqueness Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Show NoUniqueness Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Pretty NoUniqueness Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

SetType Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Typed Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Type -> Type Source #

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (PatElemT Type) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (PatElemT (MemInfo SubExp NoUniqueness ret)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (Param (MemInfo SubExp NoUniqueness ret)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (ParamT Type) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ParamT Type -> Doc #

pprPrec :: Int -> ParamT Type -> Doc #

pprList :: [ParamT Type] -> Doc #

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

Defined in Futhark.Representation.ExplicitMemory

Typed (MemInfo SubExp NoUniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

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
Functor ShapeBase Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Pretty ExtShape Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ExtShape -> Doc #

pprPrec :: Int -> ExtShape -> Doc #

pprList :: [ExtShape] -> Doc #

Pretty Shape Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Shape -> Doc #

pprPrec :: Int -> Shape -> Doc #

pprList :: [Shape] -> Doc #

SetType Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Type -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

Defined in Futhark.Representation.AST.Syntax.Core

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

Defined in Futhark.Representation.AST.Syntax.Core

Semigroup (ShapeBase d) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

Monoid (ShapeBase d) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Pretty (PatElemT Type) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (ParamT DeclType) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (ParamT Type) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ParamT Type -> Doc #

pprPrec :: Int -> ParamT Type -> Doc #

pprList :: [ParamT Type] -> Doc #

ArrayShape (ShapeBase SubExp) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

ArrayShape (ShapeBase ExtSize) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

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

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: ShapeBase d -> Names Source #

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

Defined in Futhark.Transform.Substitute

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

Defined in Futhark.Transform.Rename

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

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: SimplifiableLore lore => ShapeBase d -> SimpleM lore (ShapeBase d) Source #

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

Defined in Futhark.Representation.AST.Pretty

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

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: TypeBase Shape u -> Doc #

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

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

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.

data Ext a Source #

Something that may be existential.

Constructors

Ext Int 
Free a 
Instances
Pretty ExtShape Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ExtShape -> Doc #

pprPrec :: Int -> ExtShape -> Doc #

pprList :: [ExtShape] -> Doc #

FixExt ExtSize Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Rename ExtSize Source # 
Instance details

Defined in Futhark.Transform.Rename

Simplifiable ExtSize Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

Defined in Futhark.Representation.AST.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 #

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

show :: Ext a -> String #

showList :: [Ext a] -> ShowS #

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

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Ext a -> Doc #

pprPrec :: Int -> Ext a -> Doc #

pprList :: [Ext a] -> Doc #

ArrayShape (ShapeBase ExtSize) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: Ext d -> Names Source #

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

Defined in Futhark.Transform.Substitute

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

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

Defined in Futhark.Representation.AST.Pretty

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

Defined in Futhark.Representation.ExplicitMemory

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

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

Defined in Futhark.Representation.ExplicitMemory

type ExtSize = Ext SubExp Source #

The size of this dimension.

type ExtShape = ShapeBase ExtSize Source #

Like ShapeBase 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
Eq Rank Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Ord Rank Source # 
Instance details

Defined in Futhark.Representation.AST.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.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> Rank -> ShowS #

show :: Rank -> String #

showList :: [Rank] -> ShowS #

Semigroup Rank Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

sconcat :: NonEmpty Rank -> Rank #

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

Monoid Rank Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

mempty :: Rank #

mappend :: Rank -> Rank -> Rank #

mconcat :: [Rank] -> Rank #

ArrayShape Rank Source # 
Instance details

Defined in Futhark.Representation.AST.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.Representation.AST.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 
Instances
Eq Space Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Ord Space Source # 
Instance details

Defined in Futhark.Representation.AST.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.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> Space -> ShowS #

show :: Space -> String #

showList :: [Space] -> ShowS #

Pretty Space Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Space -> Doc #

pprPrec :: Int -> Space -> Doc #

pprList :: [Space] -> Doc #

type SpaceId = String Source #

A string representing a specific non-default memory space.

data TypeBase shape u Source #

An 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
SetType Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Type -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

Pretty (PatElemT Type) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (ParamT DeclType) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (ParamT Type) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ParamT Type -> Doc #

pprPrec :: Int -> ParamT Type -> Doc #

pprList :: [ParamT Type] -> Doc #

PrettyAnnot (PatElemT (TypeBase shape u)) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppAnnot :: PatElemT (TypeBase shape u) -> Maybe Doc Source #

PrettyAnnot (ParamT (TypeBase shape u)) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppAnnot :: ParamT (TypeBase shape u) -> Maybe Doc Source #

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

Defined in Futhark.Representation.AST.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.Representation.AST.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.Representation.AST.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.Representation.AST.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.Representation.AST.Pretty

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

Defined in Futhark.Representation.AST.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.Representation.AST.Attributes.Types

Methods

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

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: TypeBase shape u -> Names 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 #

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Ord Diet Source # 
Instance details

Defined in Futhark.Representation.AST.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.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> Diet -> ShowS #

show :: Diet -> String #

showList :: [Diet] -> ShowS #

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
Functor ErrorMsg Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Foldable ErrorMsg Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

fold :: Monoid m => ErrorMsg m -> 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.Representation.AST.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) #

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

Defined in Futhark.Representation.AST.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 #

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

show :: ErrorMsg a -> String #

showList :: [ErrorMsg a] -> ShowS #

IsString (ErrorMsg a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

fromString :: String -> ErrorMsg a #

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

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ErrorMsg a -> Doc #

pprPrec :: Int -> ErrorMsg a -> Doc #

pprList :: [ErrorMsg a] -> Doc #

data ErrorMsgPart a Source #

A part of an error message.

Constructors

ErrorString String

A literal string.

ErrorInt32 a

A run-time integer value.

Instances
Functor ErrorMsgPart Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Foldable ErrorMsgPart Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

fold :: Monoid m => ErrorMsgPart m -> 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.Representation.AST.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) #

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

Defined in Futhark.Representation.AST.Syntax.Core

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

Defined in Futhark.Representation.AST.Syntax.Core

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

Defined in Futhark.Representation.AST.Syntax.Core

IsString (ErrorMsgPart a) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Values

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Ord Ident Source # 
Instance details

Defined in Futhark.Representation.AST.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.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Pretty Ident Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Ident -> Doc #

pprPrec :: Int -> Ident -> Doc #

pprList :: [Ident] -> Doc #

Typed Ident Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Ident -> Type Source #

FreeIn Ident Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: Ident -> Names Source #

Substitute Ident Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename Ident Source # 
Instance details

Defined in Futhark.Transform.Rename

newtype Certificates Source #

A list of names used for certificates in some expressions.

Constructors

Certificates 

Fields

Instances
Eq Certificates Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Ord Certificates Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Show Certificates Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Semigroup Certificates Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Monoid Certificates Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Pretty Certificates Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

FreeIn Certificates Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Substitute Certificates Source # 
Instance details

Defined in Futhark.Transform.Substitute

Rename Certificates Source # 
Instance details

Defined in Futhark.Transform.Rename

Simplifiable Certificates Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

MonadWriter Certificates (SimpleM lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Engine

Methods

writer :: (a, Certificates) -> SimpleM lore a #

tell :: Certificates -> SimpleM lore () #

listen :: SimpleM lore a -> SimpleM lore (a, Certificates) #

pass :: SimpleM lore (a, Certificates -> Certificates) -> SimpleM lore 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
Eq SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Ord SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Show SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Pretty SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: SubExp -> Doc #

pprPrec :: Int -> SubExp -> Doc #

pprList :: [SubExp] -> Doc #

Pretty ExtShape Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ExtShape -> Doc #

pprPrec :: Int -> ExtShape -> Doc #

pprList :: [ExtShape] -> Doc #

Pretty Shape Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: Shape -> Doc #

pprPrec :: Int -> Shape -> Doc #

pprList :: [Shape] -> Doc #

FixExt ExtSize Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

SetType Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

DeclExtTyped DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

ExtTyped ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

DeclTyped DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Typed DeclType Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: DeclType -> Type Source #

Typed Type Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Type -> Type Source #

IsRetType DeclExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsRetType FunReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

IsBodyType ExtType Source # 
Instance details

Defined in Futhark.Representation.AST.RetType

IsBodyType BodyReturns Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

FreeIn SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: SubExp -> Names 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

RangeOf SubExp Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangeOf :: SubExp -> Range Source #

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

Methods

toExp :: SubExp -> ImpM lore op Exp Source #

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

Pretty (PatElemT Type) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (PatElemT (MemInfo SubExp NoUniqueness ret)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (Param (MemInfo SubExp Uniqueness ret)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (Param (MemInfo SubExp NoUniqueness ret)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (ParamT DeclType) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (ParamT Type) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ParamT Type -> Doc #

pprPrec :: Int -> ParamT Type -> Doc #

pprList :: [ParamT Type] -> Doc #

ArrayShape (ShapeBase SubExp) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

ArrayShape (ShapeBase ExtSize) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

(Pretty u, Pretty r) => PrettyAnnot (PatElemT (MemInfo SubExp u r)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

(Pretty u, Pretty r) => PrettyAnnot (ParamT (MemInfo SubExp u r)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Simplifiable [FunReturns] Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

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

Defined in Futhark.Representation.AST.Pretty

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

Defined in Futhark.Representation.AST.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.Representation.ExplicitMemory

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

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

Defined in Futhark.Representation.ExplicitMemory

DeclTyped (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Typed (MemInfo SubExp Uniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Typed (MemInfo SubExp NoUniqueness ret) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

data ParamT attr Source #

A function parameter.

Constructors

Param 

Fields

Instances
Functor ParamT Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Foldable ParamT Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

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

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

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

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

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

toList :: ParamT a -> [a] #

null :: ParamT a -> Bool #

length :: ParamT a -> Int #

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

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

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

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

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

Traversable ParamT Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

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

Eq attr => Eq (ParamT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

(==) :: ParamT attr -> ParamT attr -> Bool #

(/=) :: ParamT attr -> ParamT attr -> Bool #

Ord attr => Ord (ParamT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: ParamT attr -> ParamT attr -> Ordering #

(<) :: ParamT attr -> ParamT attr -> Bool #

(<=) :: ParamT attr -> ParamT attr -> Bool #

(>) :: ParamT attr -> ParamT attr -> Bool #

(>=) :: ParamT attr -> ParamT attr -> Bool #

max :: ParamT attr -> ParamT attr -> ParamT attr #

min :: ParamT attr -> ParamT attr -> ParamT attr #

Show attr => Show (ParamT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

showsPrec :: Int -> ParamT attr -> ShowS #

show :: ParamT attr -> String #

showList :: [ParamT attr] -> ShowS #

Pretty (Param (MemInfo SubExp Uniqueness ret)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (Param (MemInfo SubExp NoUniqueness ret)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

Pretty (ParamT b) => Pretty (ParamT (a, b)) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ParamT (a, b) -> Doc #

pprPrec :: Int -> ParamT (a, b) -> Doc #

pprList :: [ParamT (a, b)] -> Doc #

Pretty (ParamT DeclType) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (ParamT Type) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: ParamT Type -> Doc #

pprPrec :: Int -> ParamT Type -> Doc #

pprList :: [ParamT Type] -> Doc #

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

Defined in Futhark.Representation.AST.Attributes.Types

Methods

declTypeOf :: Param attr -> DeclType Source #

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

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: Param attr -> Type Source #

PrettyAnnot (ParamT (TypeBase shape u)) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppAnnot :: ParamT (TypeBase shape u) -> Maybe Doc Source #

(Pretty u, Pretty r) => PrettyAnnot (ParamT (MemInfo SubExp u r)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

FreeIn attr => FreeIn (ParamT attr) Source # 
Instance details

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: ParamT attr -> Names Source #

Substitute attr => Substitute (ParamT attr) Source # 
Instance details

Defined in Futhark.Transform.Substitute

Methods

substituteNames :: Map VName VName -> ParamT attr -> ParamT attr Source #

Rename attr => Rename (ParamT attr) Source # 
Instance details

Defined in Futhark.Transform.Rename

Methods

rename :: ParamT attr -> RenameM (ParamT attr) Source #

type Param = ParamT Source #

A type alias for namespace control.

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
Functor DimIndex Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

Foldable DimIndex Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

fold :: Monoid m => DimIndex m -> 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.Representation.AST.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) #

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

Defined in Futhark.Representation.AST.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 #

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

show :: DimIndex d -> String #

showList :: [DimIndex d] -> ShowS #

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

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: DimIndex d -> Doc #

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

pprList :: [DimIndex d] -> Doc #

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: DimIndex d -> Names Source #

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

Defined in Futhark.Transform.Substitute

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

Defined in Futhark.Transform.Rename

Methods

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

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

Defined in Futhark.Optimise.Simplify.Engine

Methods

simplify :: SimplifiableLore lore => DimIndex d -> SimpleM lore (DimIndex d) Source #

type Slice d = [DimIndex d] Source #

A list of DimFixs, 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.

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.

data PatElemT attr Source #

An element of a pattern - consisting of a name (essentially a pair of the name and type) and an addditional parametric attribute. This attribute is what is expected to contain the type of the resulting variable.

Constructors

PatElem 

Fields

Instances
Functor PatElemT Source # 
Instance details

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

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

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

compare :: PatElemT attr -> PatElemT attr -> Ordering #

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

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

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

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

max :: PatElemT attr -> PatElemT attr -> PatElemT attr #

min :: PatElemT attr -> PatElemT attr -> PatElemT attr #

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

Defined in Futhark.Representation.AST.Syntax.Core

Methods

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

show :: PatElemT attr -> String #

showList :: [PatElemT attr] -> ShowS #

Pretty (PatElemT b) => Pretty (PatElemT (a, b)) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppr :: PatElemT (a, b) -> Doc #

pprPrec :: Int -> PatElemT (a, b) -> Doc #

pprList :: [PatElemT (a, b)] -> Doc #

Pretty (PatElemT Type) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Pretty (PatElemT (MemInfo SubExp NoUniqueness ret)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

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

Defined in Futhark.Representation.AST.Attributes.Types

Methods

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

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

Defined in Futhark.Representation.AST.Attributes.Types

Methods

typeOf :: PatElemT attr -> Type Source #

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

Defined in Futhark.Representation.Ranges

Methods

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

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

Defined in Futhark.Representation.Aliases

Methods

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

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

Defined in Futhark.Optimise.Simplify.Lore

Methods

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

PrettyAnnot (PatElemT (TypeBase shape u)) Source # 
Instance details

Defined in Futhark.Representation.AST.Pretty

Methods

ppAnnot :: PatElemT (TypeBase shape u) -> Maybe Doc Source #

(Pretty u, Pretty r) => PrettyAnnot (PatElemT (MemInfo SubExp u r)) Source # 
Instance details

Defined in Futhark.Representation.ExplicitMemory

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

Defined in Futhark.Representation.AST.Attributes.Names

Methods

freeIn :: PatElemT attr -> Names Source #

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

Defined in Futhark.Transform.Substitute

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

Defined in Futhark.Transform.Rename

Methods

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

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

Defined in Futhark.Representation.AST.Attributes.Aliases

Methods

aliasesOf :: PatElemT attr -> Names Source #

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

Defined in Futhark.Representation.AST.Attributes.Ranges

Methods

rangeOf :: PatElemT attr -> Range Source #

Miscellaneous

type Names = Set VName Source #

A set of names.