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

Safe HaskellNone
LanguageHaskell2010

Language.Futhark.Syntax

Contents

Description

This is an ever-changing syntax representation for Futhark. Some types, such as Exp, are parametrised by type and name representation. See the https://futhark.readthedocs.org for a language reference, or this module may be a little hard to understand.

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

An integer type, ordered by size. Note that signedness is not a property of the type, but a property of the operations performed on values of these types.

Constructors

Int8 
Int16 
Int32 
Int64 

data FloatType Source #

A floating point type.

Constructors

Float32 
Float64 
Instances
Bounded FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Enum FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Eq FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Ord FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Show FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Pretty FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: FloatType -> Doc #

pprPrec :: Int -> FloatType -> Doc #

pprList :: [FloatType] -> Doc #

data PrimType Source #

Low-level primitive types.

Instances
Eq PrimType Source # 
Instance details

Defined in Language.Futhark.Syntax

Ord PrimType Source # 
Instance details

Defined in Language.Futhark.Syntax

Show PrimType Source # 
Instance details

Defined in Language.Futhark.Syntax

Pretty PrimType Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

ppr :: PrimType -> Doc #

pprPrec :: Int -> PrimType -> Doc #

pprList :: [PrimType] -> Doc #

class (Eq dim, Ord dim) => ArrayDim dim where Source #

Methods

unifyDims :: dim -> dim -> Maybe dim Source #

unifyDims x y combines x and y to contain their maximum common information, and fails if they conflict.

Instances
ArrayDim () Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

unifyDims :: () -> () -> Maybe () Source #

(Eq vn, Ord vn) => ArrayDim (DimDecl vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

unifyDims :: DimDecl vn -> DimDecl vn -> Maybe (DimDecl vn) Source #

data DimDecl vn Source #

Declaration of a dimension size.

Constructors

NamedDim (QualName vn)

The size of the dimension is this name, which must be in scope. In a return type, this will give rise to an assertion.

ConstDim Int

The size is a constant.

AnyDim

No dimension declaration.

Instances
Functor DimDecl Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

Foldable DimDecl Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

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

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

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

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

toList :: DimDecl a -> [a] #

null :: DimDecl a -> Bool #

length :: DimDecl a -> Int #

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

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

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

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

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

Traversable DimDecl Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

ASTMappable StructType Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable PatternType Source # 
Instance details

Defined in Language.Futhark.Traversals

Eq vn => Eq (DimDecl vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

(==) :: DimDecl vn -> DimDecl vn -> Bool #

(/=) :: DimDecl vn -> DimDecl vn -> Bool #

Ord vn => Ord (DimDecl vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

compare :: DimDecl vn -> DimDecl vn -> Ordering #

(<) :: DimDecl vn -> DimDecl vn -> Bool #

(<=) :: DimDecl vn -> DimDecl vn -> Bool #

(>) :: DimDecl vn -> DimDecl vn -> Bool #

(>=) :: DimDecl vn -> DimDecl vn -> Bool #

max :: DimDecl vn -> DimDecl vn -> DimDecl vn #

min :: DimDecl vn -> DimDecl vn -> DimDecl vn #

Show vn => Show (DimDecl vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> DimDecl vn -> ShowS #

show :: DimDecl vn -> String #

showList :: [DimDecl vn] -> ShowS #

IsName vn => Pretty (ShapeDecl (DimDecl vn)) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: ShapeDecl (DimDecl vn) -> Doc #

pprPrec :: Int -> ShapeDecl (DimDecl vn) -> Doc #

pprList :: [ShapeDecl (DimDecl vn)] -> Doc #

IsName vn => Pretty (DimDecl vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: DimDecl vn -> Doc #

pprPrec :: Int -> DimDecl vn -> Doc #

pprList :: [DimDecl vn] -> Doc #

(Eq vn, Ord vn) => ArrayDim (DimDecl vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

unifyDims :: DimDecl vn -> DimDecl vn -> Maybe (DimDecl vn) Source #

ASTMappable (DimDecl VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

Methods

astMap :: Monad m => ASTMapper m -> DimDecl VName -> m (DimDecl VName) Source #

Substitutable (TypeBase (DimDecl VName) ()) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

Substitutable (TypeBase (DimDecl VName) Aliasing) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

newtype ShapeDecl dim Source #

The size of an array type is a list of its dimension sizes. If Nothing, that dimension is of a (statically) unknown size.

Constructors

ShapeDecl 

Fields

Instances
Functor ShapeDecl Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

Foldable ShapeDecl Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

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

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

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

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

toList :: ShapeDecl a -> [a] #

null :: ShapeDecl a -> Bool #

length :: ShapeDecl a -> Int #

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

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

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

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

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

Traversable ShapeDecl Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

Eq dim => Eq (ShapeDecl dim) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

(==) :: ShapeDecl dim -> ShapeDecl dim -> Bool #

(/=) :: ShapeDecl dim -> ShapeDecl dim -> Bool #

Ord dim => Ord (ShapeDecl dim) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

compare :: ShapeDecl dim -> ShapeDecl dim -> Ordering #

(<) :: ShapeDecl dim -> ShapeDecl dim -> Bool #

(<=) :: ShapeDecl dim -> ShapeDecl dim -> Bool #

(>) :: ShapeDecl dim -> ShapeDecl dim -> Bool #

(>=) :: ShapeDecl dim -> ShapeDecl dim -> Bool #

max :: ShapeDecl dim -> ShapeDecl dim -> ShapeDecl dim #

min :: ShapeDecl dim -> ShapeDecl dim -> ShapeDecl dim #

Show dim => Show (ShapeDecl dim) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> ShapeDecl dim -> ShowS #

show :: ShapeDecl dim -> String #

showList :: [ShapeDecl dim] -> ShowS #

Semigroup (ShapeDecl dim) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

(<>) :: ShapeDecl dim -> ShapeDecl dim -> ShapeDecl dim #

sconcat :: NonEmpty (ShapeDecl dim) -> ShapeDecl dim #

stimes :: Integral b => b -> ShapeDecl dim -> ShapeDecl dim #

Monoid (ShapeDecl dim) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

mempty :: ShapeDecl dim #

mappend :: ShapeDecl dim -> ShapeDecl dim -> ShapeDecl dim #

mconcat :: [ShapeDecl dim] -> ShapeDecl dim #

Pretty (ShapeDecl ()) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: ShapeDecl () -> Doc #

pprPrec :: Int -> ShapeDecl () -> Doc #

pprList :: [ShapeDecl ()] -> Doc #

IsName vn => Pretty (ShapeDecl (DimDecl vn)) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: ShapeDecl (DimDecl vn) -> Doc #

pprPrec :: Int -> ShapeDecl (DimDecl vn) -> Doc #

pprList :: [ShapeDecl (DimDecl vn)] -> Doc #

shapeRank :: ShapeDecl dim -> Int Source #

The number of dimensions contained in a shape.

stripDims :: Int -> ShapeDecl dim -> Maybe (ShapeDecl dim) Source #

stripDims n shape strips the outer n dimensions from shape, returning Nothing if this would result in zero or fewer dimensions.

unifyShapes :: ArrayDim dim => ShapeDecl dim -> ShapeDecl dim -> Maybe (ShapeDecl dim) Source #

unifyShapes x y combines x and y to contain their maximum common information, and fails if they conflict.

data TypeName Source #

A type name consists of qualifiers (for error messages) and a VName (for equality checking).

Constructors

TypeName 

Fields

data TypeBase dim as Source #

An expanded Futhark type is either an array, a prim type, a tuple, or a type variable. When comparing types for equality with ==, aliases are ignored, but dimensions much match. Function parameter names are ignored.

Constructors

Prim PrimType 
Enum [Name] 
Array as Uniqueness (ArrayElemTypeBase dim) (ShapeDecl dim) 
Record (Map Name (TypeBase dim as)) 
TypeVar as Uniqueness TypeName [TypeArg dim] 
Arrow as (Maybe VName) (TypeBase dim as) (TypeBase dim as)

The aliasing corresponds to the lexical closure of the function.

Instances
Bitraversable TypeBase Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

Bifoldable TypeBase Source # 
Instance details

Defined in Language.Futhark.Syntax

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 Language.Futhark.Syntax

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 #

ASTMappable StructType Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable PatternType Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable CompType Source # 
Instance details

Defined in Language.Futhark.Traversals

Methods

astMap :: Monad m => ASTMapper m -> CompType -> m CompType Source #

(Eq dim, Eq as) => Eq (TypeBase dim as) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

(==) :: TypeBase dim as -> TypeBase dim as -> Bool #

(/=) :: TypeBase dim as -> TypeBase dim as -> Bool #

(Show as, Show dim) => Show (TypeBase dim as) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> TypeBase dim as -> ShowS #

show :: TypeBase dim as -> String #

showList :: [TypeBase dim as] -> ShowS #

Pretty (ShapeDecl dim) => Pretty (TypeBase dim as) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: TypeBase dim as -> Doc #

pprPrec :: Int -> TypeBase dim as -> Doc #

pprList :: [TypeBase dim as] -> Doc #

ASTMappable (TypeBase () ()) Source # 
Instance details

Defined in Language.Futhark.Traversals

Methods

astMap :: Monad m => ASTMapper m -> TypeBase () () -> m (TypeBase () ()) Source #

Substitutable (TypeBase () ()) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

Methods

applySubst :: (VName -> Maybe (Subst (TypeBase () ()))) -> TypeBase () () -> TypeBase () () Source #

Substitutable (TypeBase () Aliasing) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

Substitutable (TypeBase (DimDecl VName) ()) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

Substitutable (TypeBase (DimDecl VName) Aliasing) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

data TypeArg dim Source #

Constructors

TypeArgDim dim SrcLoc 
TypeArgType (TypeBase dim ()) SrcLoc 
Instances
Functor TypeArg Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

Foldable TypeArg Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

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

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

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

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

toList :: TypeArg a -> [a] #

null :: TypeArg a -> Bool #

length :: TypeArg a -> Int #

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

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

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

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

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

Traversable TypeArg Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

Eq dim => Eq (TypeArg dim) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

(==) :: TypeArg dim -> TypeArg dim -> Bool #

(/=) :: TypeArg dim -> TypeArg dim -> Bool #

Show dim => Show (TypeArg dim) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> TypeArg dim -> ShowS #

show :: TypeArg dim -> String #

showList :: [TypeArg dim] -> ShowS #

Pretty (ShapeDecl dim) => Pretty (TypeArg dim) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: TypeArg dim -> Doc #

pprPrec :: Int -> TypeArg dim -> Doc #

pprList :: [TypeArg dim] -> Doc #

data TypeExp vn Source #

An unstructured type with type variables and possibly shape declarations - this is what the user types in the source program.

Instances
Eq vn => Eq (TypeExp vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

(==) :: TypeExp vn -> TypeExp vn -> Bool #

(/=) :: TypeExp vn -> TypeExp vn -> Bool #

Show vn => Show (TypeExp vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> TypeExp vn -> ShowS #

show :: TypeExp vn -> String #

showList :: [TypeExp vn] -> ShowS #

(Eq vn, IsName vn) => Pretty (TypeExp vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: TypeExp vn -> Doc #

pprPrec :: Int -> TypeExp vn -> Doc #

pprList :: [TypeExp vn] -> Doc #

Located (TypeExp vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: TypeExp vn -> Loc #

locOfList :: [TypeExp vn] -> Loc #

ASTMappable (TypeExp VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

Methods

astMap :: Monad m => ASTMapper m -> TypeExp VName -> m (TypeExp VName) Source #

data TypeArgExp vn Source #

Instances
Eq vn => Eq (TypeArgExp vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

(==) :: TypeArgExp vn -> TypeArgExp vn -> Bool #

(/=) :: TypeArgExp vn -> TypeArgExp vn -> Bool #

Show vn => Show (TypeArgExp vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> TypeArgExp vn -> ShowS #

show :: TypeArgExp vn -> String #

showList :: [TypeArgExp vn] -> ShowS #

(Eq vn, IsName vn) => Pretty (TypeArgExp vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: TypeArgExp vn -> Doc #

pprPrec :: Int -> TypeArgExp vn -> Doc #

pprList :: [TypeArgExp vn] -> Doc #

Located (TypeArgExp vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: TypeArgExp vn -> Loc #

locOfList :: [TypeArgExp vn] -> Loc #

ASTMappable (TypeArgExp VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

data RecordArrayElemTypeBase dim Source #

Types that can be elements of tuple-arrays.

Instances
Functor RecordArrayElemTypeBase Source # 
Instance details

Defined in Language.Futhark.Syntax

Foldable RecordArrayElemTypeBase Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

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

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

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

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

toList :: RecordArrayElemTypeBase a -> [a] #

null :: RecordArrayElemTypeBase a -> Bool #

length :: RecordArrayElemTypeBase a -> Int #

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

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

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

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

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

Traversable RecordArrayElemTypeBase Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq dim => Eq (RecordArrayElemTypeBase dim) Source # 
Instance details

Defined in Language.Futhark.Syntax

Show dim => Show (RecordArrayElemTypeBase dim) Source # 
Instance details

Defined in Language.Futhark.Syntax

Pretty (ShapeDecl dim) => Pretty (RecordArrayElemTypeBase dim) Source # 
Instance details

Defined in Language.Futhark.Pretty

data ArrayElemTypeBase dim Source #

Instances
Functor ArrayElemTypeBase Source # 
Instance details

Defined in Language.Futhark.Syntax

Foldable ArrayElemTypeBase Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

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

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

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

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

toList :: ArrayElemTypeBase a -> [a] #

null :: ArrayElemTypeBase a -> Bool #

length :: ArrayElemTypeBase a -> Int #

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

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

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

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

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

Traversable ArrayElemTypeBase Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

Eq dim => Eq (ArrayElemTypeBase dim) Source # 
Instance details

Defined in Language.Futhark.Syntax

Show dim => Show (ArrayElemTypeBase dim) Source # 
Instance details

Defined in Language.Futhark.Syntax

Pretty (ShapeDecl dim) => Pretty (ArrayElemTypeBase dim) Source # 
Instance details

Defined in Language.Futhark.Pretty

type CompType = TypeBase () Aliasing Source #

A type with aliasing information and no shape annotations, used for describing the type of a computation.

type PatternType = TypeBase (DimDecl VName) Aliasing Source #

A type with aliasing information and shape annotations, used for describing the type of a pattern.

type StructType = TypeBase (DimDecl VName) () Source #

A "structural" type with shape annotations and no aliasing information, used for declarations.

data Diet Source #

Information about which parts of a value/type are consumed.

Constructors

RecordDiet (Map Name Diet)

Consumes these fields in the record.

FuncDiet Diet Diet

A function that consumes its argument(s) like this. The final Diet should always be Observe, as there is no way for a function to consume its return value.

Consume

Consumes this value.

Observe

Only observes value in this position, does not consume.

Instances
Eq Diet Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

Show Diet Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> Diet -> ShowS #

show :: Diet -> String #

showList :: [Diet] -> ShowS #

data TypeDeclBase f vn Source #

A declaration of the type of something.

Constructors

TypeDecl 

Fields

Instances
Showable f vn => Show (TypeDeclBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> TypeDeclBase f vn -> ShowS #

show :: TypeDeclBase f vn -> String #

showList :: [TypeDeclBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (TypeDeclBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: TypeDeclBase f vn -> Doc #

pprPrec :: Int -> TypeDeclBase f vn -> Doc #

pprList :: [TypeDeclBase f vn] -> Doc #

Located (TypeDeclBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: TypeDeclBase f vn -> Loc #

locOfList :: [TypeDeclBase f vn] -> Loc #

ASTMappable (TypeDeclBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

Values

class IsPrimValue v where Source #

Methods

primValue :: v -> PrimValue Source #

Instances
IsPrimValue Bool Source # 
Instance details

Defined in Language.Futhark.Syntax

IsPrimValue Double Source # 
Instance details

Defined in Language.Futhark.Syntax

IsPrimValue Float Source # 
Instance details

Defined in Language.Futhark.Syntax

IsPrimValue Int Source # 
Instance details

Defined in Language.Futhark.Syntax

IsPrimValue Int8 Source # 
Instance details

Defined in Language.Futhark.Syntax

IsPrimValue Int16 Source # 
Instance details

Defined in Language.Futhark.Syntax

IsPrimValue Int32 Source # 
Instance details

Defined in Language.Futhark.Syntax

IsPrimValue Int64 Source # 
Instance details

Defined in Language.Futhark.Syntax

IsPrimValue Word8 Source # 
Instance details

Defined in Language.Futhark.Syntax

IsPrimValue Word16 Source # 
Instance details

Defined in Language.Futhark.Syntax

IsPrimValue Word32 Source # 
Instance details

Defined in Language.Futhark.Syntax

IsPrimValue Word64 Source # 
Instance details

Defined in Language.Futhark.Syntax

data Value Source #

Simple Futhark values. Values are fully evaluated and their type is always unambiguous.

Constructors

PrimValue !PrimValue 
ArrayValue !(Array Int Value) (TypeBase () ())

It is assumed that the array is 0-indexed. The type is the full type.

Instances
Eq Value Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

Show Value Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Pretty Value Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: Value -> Doc #

pprPrec :: Int -> Value -> Doc #

pprList :: [Value] -> Doc #

Abstract syntax tree

data BinOp Source #

Default binary operators.

Constructors

Backtick

A pseudo-operator standing in for any normal identifier used as an operator (they all have the same fixity). Binary Ops for Numbers

Plus 
Minus 
Pow 
Times 
Divide 
Mod 
Quot 
Rem 
ShiftR 
ShiftL 
Band 
Xor 
Bor 
LogAnd 
LogOr 
Equal 
NotEqual 
Less 
Leq 
Greater 
Geq 
PipeRight
|>
PipeLeft

<| Misc

Instances
Bounded BinOp Source # 
Instance details

Defined in Language.Futhark.Syntax

Enum BinOp Source # 
Instance details

Defined in Language.Futhark.Syntax

Eq BinOp Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

Ord BinOp Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

compare :: BinOp -> BinOp -> Ordering #

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

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

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

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

max :: BinOp -> BinOp -> BinOp #

min :: BinOp -> BinOp -> BinOp #

Show BinOp Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

Pretty BinOp Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

ppr :: BinOp -> Doc #

pprPrec :: Int -> BinOp -> Doc #

pprList :: [BinOp] -> Doc #

data IdentBase f vn Source #

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

Constructors

Ident 
Instances
Eq vn => Eq (IdentBase ty vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

(==) :: IdentBase ty vn -> IdentBase ty vn -> Bool #

(/=) :: IdentBase ty vn -> IdentBase ty vn -> Bool #

Ord vn => Ord (IdentBase ty vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

compare :: IdentBase ty vn -> IdentBase ty vn -> Ordering #

(<) :: IdentBase ty vn -> IdentBase ty vn -> Bool #

(<=) :: IdentBase ty vn -> IdentBase ty vn -> Bool #

(>) :: IdentBase ty vn -> IdentBase ty vn -> Bool #

(>=) :: IdentBase ty vn -> IdentBase ty vn -> Bool #

max :: IdentBase ty vn -> IdentBase ty vn -> IdentBase ty vn #

min :: IdentBase ty vn -> IdentBase ty vn -> IdentBase ty vn #

Showable f vn => Show (IdentBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> IdentBase f vn -> ShowS #

show :: IdentBase f vn -> String #

showList :: [IdentBase f vn] -> ShowS #

IsName vn => Pretty (IdentBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: IdentBase f vn -> Doc #

pprPrec :: Int -> IdentBase f vn -> Doc #

pprList :: [IdentBase f vn] -> Doc #

Located (IdentBase ty vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: IdentBase ty vn -> Loc #

locOfList :: [IdentBase ty vn] -> Loc #

ASTMappable (IdentBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

data Inclusiveness a Source #

Whether a bound for an end-point of a DimSlice or a range literal is inclusive or exclusive.

Constructors

DownToExclusive a 
ToInclusive a

May be "down to" if step is negative.

UpToExclusive a 
Instances
Functor Inclusiveness Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

Foldable Inclusiveness Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

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

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

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

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

toList :: Inclusiveness a -> [a] #

null :: Inclusiveness a -> Bool #

length :: Inclusiveness a -> Int #

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

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

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

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

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

Traversable Inclusiveness Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

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

Defined in Language.Futhark.Syntax

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

Defined in Language.Futhark.Syntax

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

Defined in Language.Futhark.Syntax

Located a => Located (Inclusiveness a) Source # 
Instance details

Defined in Language.Futhark.Syntax

data DimIndexBase f vn Source #

An indexing of a single dimension.

Constructors

DimFix (ExpBase f vn) 
DimSlice (Maybe (ExpBase f vn)) (Maybe (ExpBase f vn)) (Maybe (ExpBase f vn)) 
Instances
Showable f vn => Show (DimIndexBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> DimIndexBase f vn -> ShowS #

show :: DimIndexBase f vn -> String #

showList :: [DimIndexBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (DimIndexBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: DimIndexBase f vn -> Doc #

pprPrec :: Int -> DimIndexBase f vn -> Doc #

pprList :: [DimIndexBase f vn] -> Doc #

ASTMappable (DimIndexBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

data ExpBase f vn Source #

The Futhark expression language.

In a value of type Exp f vn, annotations are wrapped in the functor f, and all names are of type vn.

This allows us to encode whether or not the expression has been type-checked in the Haskell type of the expression. Specifically, the parser will produce expressions of type Exp NoInfo Name, and the type checker will convert these to Exp Info VName, in which type information is always present and all names are unique.

Constructors

Literal PrimValue SrcLoc 
IntLit Integer (f (TypeBase () ())) SrcLoc

A polymorphic integral literal.

FloatLit Double (f (TypeBase () ())) SrcLoc

A polymorphic decimal literal.

Parens (ExpBase f vn) SrcLoc

A parenthesized expression.

QualParens (QualName vn) (ExpBase f vn) SrcLoc 
TupLit [ExpBase f vn] SrcLoc

Tuple literals, e.g., {1+3, {x, y+z}}.

RecordLit [FieldBase f vn] SrcLoc

Record literals, e.g. {x=2,y=3,z}.

ArrayLit [ExpBase f vn] (f CompType) SrcLoc

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

Range (ExpBase f vn) (Maybe (ExpBase f vn)) (Inclusiveness (ExpBase f vn)) (f CompType) SrcLoc 
Var (QualName vn) (f PatternType) SrcLoc 
Ascript (ExpBase f vn) (TypeDeclBase f vn) SrcLoc

Type ascription: e : t.

LetPat [TypeParamBase vn] (PatternBase f vn) (ExpBase f vn) (ExpBase f vn) SrcLoc 
LetFun vn ([TypeParamBase vn], [PatternBase f vn], Maybe (TypeExp vn), f StructType, ExpBase f vn) (ExpBase f vn) SrcLoc 
If (ExpBase f vn) (ExpBase f vn) (ExpBase f vn) (f CompType) SrcLoc 
Apply (ExpBase f vn) (ExpBase f vn) (f Diet) (f PatternType) SrcLoc 
Negate (ExpBase f vn) SrcLoc

Numeric negation (ugly special case; Haskell did it first).

Lambda [TypeParamBase vn] [PatternBase f vn] (ExpBase f vn) (Maybe (TypeDeclBase f vn)) (f (Aliasing, StructType)) SrcLoc 
OpSection (QualName vn) (f PatternType) SrcLoc

+; first two types are operands, third is result.

OpSectionLeft (QualName vn) (f PatternType) (ExpBase f vn) (f StructType, f StructType) (f PatternType) SrcLoc

2+; first type is operand, second is result.

OpSectionRight (QualName vn) (f PatternType) (ExpBase f vn) (f StructType, f StructType) (f PatternType) SrcLoc

+2; first type is operand, second is result.

ProjectSection [Name] (f PatternType) SrcLoc

Field projection as a section: (.x.y.z).

IndexSection [DimIndexBase f vn] (f PatternType) SrcLoc

Array indexing as a section: (.[i,j]).

DoLoop [TypeParamBase vn] (PatternBase f vn) (ExpBase f vn) (LoopFormBase f vn) (ExpBase f vn) SrcLoc 
BinOp (QualName vn) (f PatternType) (ExpBase f vn, f StructType) (ExpBase f vn, f StructType) (f PatternType) SrcLoc 
Project Name (ExpBase f vn) (f CompType) SrcLoc 
LetWith (IdentBase f vn) (IdentBase f vn) [DimIndexBase f vn] (ExpBase f vn) (ExpBase f vn) SrcLoc 
Index (ExpBase f vn) [DimIndexBase f vn] (f CompType) SrcLoc 
Update (ExpBase f vn) [DimIndexBase f vn] (ExpBase f vn) SrcLoc 
RecordUpdate (ExpBase f vn) [Name] (ExpBase f vn) (f PatternType) SrcLoc 
Map (ExpBase f vn) (ExpBase f vn) (f CompType) SrcLoc

map (+1) [1, 2, ..., n] = [2, 3, ..., n+1].

Reduce Commutativity (ExpBase f vn) (ExpBase f vn) (ExpBase f vn) SrcLoc

reduce (+) 0 ([1,2,...,n]) = (0+1+2+...+n).

GenReduce (ExpBase f vn) (ExpBase f vn) (ExpBase f vn) (ExpBase f vn) (ExpBase f vn) SrcLoc
gen_reduce 1,1,1 0 [1,1,1] [1,1,1] = [4,1,1]
Scan (ExpBase f vn) (ExpBase f vn) (ExpBase f vn) SrcLoc

scan (+) 0 ([ 1, 2, 3 ]) = [ 1, 3, 6 ].

Filter (ExpBase f vn) (ExpBase f vn) SrcLoc

Return those elements of the array that satisfy the predicate.

Partition Int (ExpBase f vn) (ExpBase f vn) SrcLoc

partition k f a, where f returns an integer, returns a tuple (a', is) that describes a partitioning of a into n equivalence classes. Here, a' is a re-ordering of a, and is is an array of k offsets into a'.

Stream (StreamForm f vn) (ExpBase f vn) (ExpBase f vn) SrcLoc

Streaming: intuitively, this gives a size-parameterized composition for SOACs that cannot be fused, e.g., due to scan. For example, assuming A : [int], f : int->int, g : real->real, the code: let x = map(f,A) in let y = scan(op+,0,x) in map(g,y) can be re-written (streamed) in the source-Futhark language as: let (acc, z) = stream (fn (int,[real]) (real chunk, real acc, [int] a) => let x = map (f, A ) let y0= scan(op +, 0, x ) let y = map (op +(acc), y0) ( acc+y0[chunk-1], map(g, y) ) ) 0 A where (i) chunk is a symbolic int denoting the chunk size, (ii) 0 is the initial value of the accumulator, which allows the streaming of scan. Finally, the unnamed function (fn...) implements the a fold that: computes the accumulator of scan, as defined inside its body, AND implicitly concatenates each of the result arrays across the iteration space. In essence, sequential codegen can choose chunk = 1 and thus eliminate the SOACs on the outermost level, while parallel codegen may choose the maximal chunk size that still satisfies the memory requirements of the device.

Zip Int (ExpBase f vn) [ExpBase f vn] (f CompType) SrcLoc

Conventional zip taking nonzero arrays as arguments. All arrays must have the exact same length.

Unzip (ExpBase f vn) [f CompType] SrcLoc

Unzip that can unzip to tuples of arbitrary size. The types are the elements of the tuple.

Unsafe (ExpBase f vn) SrcLoc

Explore the Danger Zone and elide safety checks on array operations and other assertions during execution of this expression. Make really sure the code is correct.

Assert (ExpBase f vn) (ExpBase f vn) (f String) SrcLoc

Fail if the first expression does not return true, and return the value of the second expression if it does.

VConstr0 Name (f CompType) SrcLoc

An enum element, e.g., #foo.

Match (ExpBase f vn) [CaseBase f vn] (f CompType) SrcLoc

A match expression.

Instances
Showable f vn => Show (ExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> ExpBase f vn -> ShowS #

show :: ExpBase f vn -> String #

showList :: [ExpBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (ExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: ExpBase f vn -> Doc #

pprPrec :: Int -> ExpBase f vn -> Doc #

pprList :: [ExpBase f vn] -> Doc #

Located (ExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: ExpBase f vn -> Loc #

locOfList :: [ExpBase f vn] -> Loc #

ASTMappable (ExpBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

data FieldBase f vn Source #

An entry in a record literal.

Instances
Showable f vn => Show (FieldBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> FieldBase f vn -> ShowS #

show :: FieldBase f vn -> String #

showList :: [FieldBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (FieldBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: FieldBase f vn -> Doc #

pprPrec :: Int -> FieldBase f vn -> Doc #

pprList :: [FieldBase f vn] -> Doc #

Located (FieldBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: FieldBase f vn -> Loc #

locOfList :: [FieldBase f vn] -> Loc #

ASTMappable (FieldBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

data CaseBase f vn Source #

A case in a match expression.

Constructors

CasePat (PatternBase f vn) (ExpBase f vn) SrcLoc 
Instances
Showable f vn => Show (CaseBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> CaseBase f vn -> ShowS #

show :: CaseBase f vn -> String #

showList :: [CaseBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (CaseBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: CaseBase f vn -> Doc #

pprPrec :: Int -> CaseBase f vn -> Doc #

pprList :: [CaseBase f vn] -> Doc #

Located (CaseBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: CaseBase f vn -> Loc #

locOfList :: [CaseBase f vn] -> Loc #

ASTMappable (CaseBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

data LoopFormBase f vn Source #

Whether the loop is a for-loop or a while-loop.

Constructors

For (IdentBase f vn) (ExpBase f vn) 
ForIn (PatternBase f vn) (ExpBase f vn) 
While (ExpBase f vn) 
Instances
Showable f vn => Show (LoopFormBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> LoopFormBase f vn -> ShowS #

show :: LoopFormBase f vn -> String #

showList :: [LoopFormBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (LoopFormBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: LoopFormBase f vn -> Doc #

pprPrec :: Int -> LoopFormBase f vn -> Doc #

pprList :: [LoopFormBase f vn] -> Doc #

ASTMappable (LoopFormBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

data PatternBase f vn Source #

A pattern as used most places where variables are bound (function parameters, let expressions, etc).

Instances
Showable f vn => Show (PatternBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> PatternBase f vn -> ShowS #

show :: PatternBase f vn -> String #

showList :: [PatternBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (PatternBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: PatternBase f vn -> Doc #

pprPrec :: Int -> PatternBase f vn -> Doc #

pprList :: [PatternBase f vn] -> Doc #

Located (PatternBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: PatternBase f vn -> Loc #

locOfList :: [PatternBase f vn] -> Loc #

ASTMappable (PatternBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

data StreamForm f vn Source #

Instances
Showable f vn => Show (StreamForm f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> StreamForm f vn -> ShowS #

show :: StreamForm f vn -> String #

showList :: [StreamForm f vn] -> ShowS #

Module language

data SpecBase f vn Source #

Instances
Showable f vn => Show (SpecBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> SpecBase f vn -> ShowS #

show :: SpecBase f vn -> String #

showList :: [SpecBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (SpecBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: SpecBase f vn -> Doc #

pprPrec :: Int -> SpecBase f vn -> Doc #

pprList :: [SpecBase f vn] -> Doc #

Located (SpecBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: SpecBase f vn -> Loc #

locOfList :: [SpecBase f vn] -> Loc #

data SigExpBase f vn Source #

Instances
Showable f vn => Show (SigExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> SigExpBase f vn -> ShowS #

show :: SigExpBase f vn -> String #

showList :: [SigExpBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (SigExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: SigExpBase f vn -> Doc #

pprPrec :: Int -> SigExpBase f vn -> Doc #

pprList :: [SigExpBase f vn] -> Doc #

Located (SigExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: SigExpBase f vn -> Loc #

locOfList :: [SigExpBase f vn] -> Loc #

data TypeRefBase f vn Source #

A type refinement.

Constructors

TypeRef (QualName vn) [TypeParamBase vn] (TypeDeclBase f vn) SrcLoc 
Instances
Showable f vn => Show (TypeRefBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> TypeRefBase f vn -> ShowS #

show :: TypeRefBase f vn -> String #

showList :: [TypeRefBase f vn] -> ShowS #

Located (TypeRefBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: TypeRefBase f vn -> Loc #

locOfList :: [TypeRefBase f vn] -> Loc #

data SigBindBase f vn Source #

Constructors

SigBind 

Fields

Instances
Showable f vn => Show (SigBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> SigBindBase f vn -> ShowS #

show :: SigBindBase f vn -> String #

showList :: [SigBindBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (SigBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: SigBindBase f vn -> Doc #

pprPrec :: Int -> SigBindBase f vn -> Doc #

pprList :: [SigBindBase f vn] -> Doc #

Located (SigBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: SigBindBase f vn -> Loc #

locOfList :: [SigBindBase f vn] -> Loc #

data ModExpBase f vn Source #

Constructors

ModVar (QualName vn) SrcLoc 
ModParens (ModExpBase f vn) SrcLoc 
ModImport FilePath (f FilePath) SrcLoc

The contents of another file as a module.

ModDecs [DecBase f vn] SrcLoc 
ModApply (ModExpBase f vn) (ModExpBase f vn) (f (Map VName VName)) (f (Map VName VName)) SrcLoc

Functor application.

ModAscript (ModExpBase f vn) (SigExpBase f vn) (f (Map VName VName)) SrcLoc 
ModLambda (ModParamBase f vn) (Maybe (SigExpBase f vn, f (Map VName VName))) (ModExpBase f vn) SrcLoc 
Instances
Showable f vn => Show (ModExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> ModExpBase f vn -> ShowS #

show :: ModExpBase f vn -> String #

showList :: [ModExpBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (ModExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: ModExpBase f vn -> Doc #

pprPrec :: Int -> ModExpBase f vn -> Doc #

pprList :: [ModExpBase f vn] -> Doc #

Located (ModExpBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: ModExpBase f vn -> Loc #

locOfList :: [ModExpBase f vn] -> Loc #

data ModBindBase f vn Source #

Constructors

ModBind 
Instances
Showable f vn => Show (ModBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> ModBindBase f vn -> ShowS #

show :: ModBindBase f vn -> String #

showList :: [ModBindBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (ModBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: ModBindBase f vn -> Doc #

pprPrec :: Int -> ModBindBase f vn -> Doc #

pprList :: [ModBindBase f vn] -> Doc #

Located (ModBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: ModBindBase f vn -> Loc #

locOfList :: [ModBindBase f vn] -> Loc #

data ModParamBase f vn Source #

Constructors

ModParam 
Instances
Showable f vn => Show (ModParamBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> ModParamBase f vn -> ShowS #

show :: ModParamBase f vn -> String #

showList :: [ModParamBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (ModParamBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: ModParamBase f vn -> Doc #

pprPrec :: Int -> ModParamBase f vn -> Doc #

pprList :: [ModParamBase f vn] -> Doc #

Located (ModParamBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: ModParamBase f vn -> Loc #

locOfList :: [ModParamBase f vn] -> Loc #

Definitions

data DocComment Source #

Documentation strings, including source location.

Constructors

DocComment String SrcLoc 
Instances
Show DocComment Source # 
Instance details

Defined in Language.Futhark.Syntax

Located DocComment Source # 
Instance details

Defined in Language.Futhark.Syntax

data ValBindBase f vn Source #

Function Declarations

Constructors

ValBind 
Instances
Showable f vn => Show (ValBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> ValBindBase f vn -> ShowS #

show :: ValBindBase f vn -> String #

showList :: [ValBindBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (ValBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: ValBindBase f vn -> Doc #

pprPrec :: Int -> ValBindBase f vn -> Doc #

pprList :: [ValBindBase f vn] -> Doc #

Located (ValBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: ValBindBase f vn -> Loc #

locOfList :: [ValBindBase f vn] -> Loc #

data Liftedness Source #

The liftedness of a type parameter. By the Ord instance, Unlifted is less than Lifted.

Constructors

Unlifted

May only be instantiated with a zero-order type.

Lifted

May be instantiated to a functional type.

data TypeBindBase f vn Source #

Type Declarations

Instances
Showable f vn => Show (TypeBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> TypeBindBase f vn -> ShowS #

show :: TypeBindBase f vn -> String #

showList :: [TypeBindBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (TypeBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: TypeBindBase f vn -> Doc #

pprPrec :: Int -> TypeBindBase f vn -> Doc #

pprList :: [TypeBindBase f vn] -> Doc #

Located (TypeBindBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: TypeBindBase f vn -> Loc #

locOfList :: [TypeBindBase f vn] -> Loc #

data TypeParamBase vn Source #

Constructors

TypeParamDim vn SrcLoc

A type parameter that must be a size.

TypeParamType Liftedness vn SrcLoc

A type parameter that must be a type.

Instances
Functor TypeParamBase Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

Foldable TypeParamBase Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

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

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

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

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

toList :: TypeParamBase a -> [a] #

null :: TypeParamBase a -> Bool #

length :: TypeParamBase a -> Int #

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

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

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

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

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

Traversable TypeParamBase Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

Eq vn => Eq (TypeParamBase vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Show vn => Show (TypeParamBase vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

(Eq vn, IsName vn) => Pretty (TypeParamBase vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: TypeParamBase vn -> Doc #

pprPrec :: Int -> TypeParamBase vn -> Doc #

pprList :: [TypeParamBase vn] -> Doc #

Located (TypeParamBase vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: TypeParamBase vn -> Loc #

locOfList :: [TypeParamBase vn] -> Loc #

ASTMappable (TypeParamBase VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

data ProgBase f vn Source #

The program described by a single Futhark file. May depend on other files.

Constructors

Prog 

Fields

Instances
Showable f vn => Show (ProgBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> ProgBase f vn -> ShowS #

show :: ProgBase f vn -> String #

showList :: [ProgBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (ProgBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: ProgBase f vn -> Doc #

pprPrec :: Int -> ProgBase f vn -> Doc #

pprList :: [ProgBase f vn] -> Doc #

data DecBase f vn Source #

A top-level binding.

Instances
Showable f vn => Show (DecBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> DecBase f vn -> ShowS #

show :: DecBase f vn -> String #

showList :: [DecBase f vn] -> ShowS #

(Eq vn, IsName vn, Annot f) => Pretty (DecBase f vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: DecBase f vn -> Doc #

pprPrec :: Int -> DecBase f vn -> Doc #

pprList :: [DecBase f vn] -> Doc #

Located (DecBase f vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

locOf :: DecBase f vn -> Loc #

locOfList :: [DecBase f vn] -> Loc #

Miscellaneous

data NoInfo a Source #

No information functor. Usually used for placeholder type- or aliasing information.

Constructors

NoInfo 
Instances
Functor NoInfo Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

Foldable NoInfo Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

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

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

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

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

toList :: NoInfo a -> [a] #

null :: NoInfo a -> Bool #

length :: NoInfo a -> Int #

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

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

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

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

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

Traversable NoInfo Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

Annot NoInfo Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

unAnnot :: NoInfo a -> Maybe a

Eq (NoInfo a) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

Ord (NoInfo a) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

compare :: NoInfo a -> NoInfo a -> Ordering #

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

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

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

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

max :: NoInfo a -> NoInfo a -> NoInfo a #

min :: NoInfo a -> NoInfo a -> NoInfo a #

Show (NoInfo a) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

show :: NoInfo a -> String #

showList :: [NoInfo a] -> ShowS #

newtype Info a Source #

Some information. The dual to NoInfo

Constructors

Info 

Fields

Instances
Functor Info Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

Foldable Info Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

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

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

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

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

toList :: Info a -> [a] #

null :: Info a -> Bool #

length :: Info a -> Int #

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

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

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

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

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

Traversable Info Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

Annot Info Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

unAnnot :: Info a -> Maybe a

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

Defined in Language.Futhark.Syntax

Methods

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

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

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

Defined in Language.Futhark.Syntax

Methods

compare :: Info a -> Info a -> Ordering #

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

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

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

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

max :: Info a -> Info a -> Info a #

min :: Info a -> Info a -> Info a #

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

Defined in Language.Futhark.Syntax

Methods

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

show :: Info a -> String #

showList :: [Info a] -> ShowS #

ASTMappable a => ASTMappable (Info a) Source # 
Instance details

Defined in Language.Futhark.Traversals

Methods

astMap :: Monad m => ASTMapper m -> Info a -> m (Info a) Source #

ASTMappable (PatternBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (LoopFormBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (CaseBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (FieldBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (ExpBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (DimIndexBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (IdentBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable (TypeDeclBase Info VName) Source # 
Instance details

Defined in Language.Futhark.Traversals

data Alias Source #

A variable that is aliased. Can be still in-scope, or have gone out of scope and be free. In the latter case, it behaves more like an equivalence class. See uniqueness-error18.fut for an example of why this is necessary.

Constructors

AliasBound 

Fields

AliasFree 

Fields

Instances
Eq Alias Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

Ord Alias Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

compare :: Alias -> Alias -> Ordering #

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

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

(>) :: Alias -> Alias -> Bool #

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

max :: Alias -> Alias -> Alias #

min :: Alias -> Alias -> Alias #

Show Alias Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> Alias -> ShowS #

show :: Alias -> String #

showList :: [Alias] -> ShowS #

ASTMappable PatternType Source # 
Instance details

Defined in Language.Futhark.Traversals

ASTMappable CompType Source # 
Instance details

Defined in Language.Futhark.Traversals

Methods

astMap :: Monad m => ASTMapper m -> CompType -> m CompType Source #

ASTMappable Aliasing Source # 
Instance details

Defined in Language.Futhark.Traversals

Methods

astMap :: Monad m => ASTMapper m -> Aliasing -> m Aliasing Source #

ASTMappable Alias Source # 
Instance details

Defined in Language.Futhark.Traversals

Methods

astMap :: Monad m => ASTMapper m -> Alias -> m Alias Source #

Substitutable (TypeBase () Aliasing) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

Substitutable (TypeBase (DimDecl VName) Aliasing) Source # 
Instance details

Defined in Language.Futhark.TypeChecker.Types

type Aliasing = Set Alias Source #

Aliasing for a type, which is a set of the variables that are aliased.

data QualName vn Source #

A name qualified with a breadcrumb of module accesses.

Constructors

QualName 

Fields

Instances
Functor QualName Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

Foldable QualName Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

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

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

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

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

toList :: QualName a -> [a] #

null :: QualName a -> Bool #

length :: QualName a -> Int #

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

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

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

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

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

Traversable QualName Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

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

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

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

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

Eq vn => Eq (QualName vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

(==) :: QualName vn -> QualName vn -> Bool #

(/=) :: QualName vn -> QualName vn -> Bool #

Ord vn => Ord (QualName vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

compare :: QualName vn -> QualName vn -> Ordering #

(<) :: QualName vn -> QualName vn -> Bool #

(<=) :: QualName vn -> QualName vn -> Bool #

(>) :: QualName vn -> QualName vn -> Bool #

(>=) :: QualName vn -> QualName vn -> Bool #

max :: QualName vn -> QualName vn -> QualName vn #

min :: QualName vn -> QualName vn -> QualName vn #

Show vn => Show (QualName vn) Source # 
Instance details

Defined in Language.Futhark.Syntax

Methods

showsPrec :: Int -> QualName vn -> ShowS #

show :: QualName vn -> String #

showList :: [QualName vn] -> ShowS #

IsName vn => Pretty (QualName vn) Source # 
Instance details

Defined in Language.Futhark.Pretty

Methods

ppr :: QualName vn -> Doc #

pprPrec :: Int -> QualName vn -> Doc #

pprList :: [QualName vn] -> Doc #