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

Safe HaskellNone
LanguageHaskell2010

Language.Futhark.Attributes

Contents

Description

This module provides various simple ways to query and manipulate fundamental Futhark terms, such as types and values. The intent is to keep Futhark.Language.Syntax simple, and put whatever embellishments we need here.

Synopsis

Various

data Intrinsic Source #

The nature of something predefined. These can either be monomorphic or overloaded. An overloaded builtin is a list valid types it can be instantiated with, to the parameter and result type, with Nothing representing the overloaded parameter type.

intrinsics :: Map VName Intrinsic Source #

A map of all built-ins.

maxIntrinsicTag :: Int Source #

The largest tag used by an intrinsic - this can be used to determine whether a VName refers to an intrinsic or a user-defined name.

namesToPrimTypes :: Map Name PrimType Source #

Names of primitive types to types. This is only valid if no shadowing is going on, but useful for tools.

qualName :: v -> QualName v Source #

Create a name with no qualifiers from a name.

qualify :: v -> QualName v -> QualName v Source #

Add another qualifier (at the head) to a qualified name.

typeName :: VName -> TypeName Source #

Create a type name name with no qualifiers from a VName.

leadingOperator :: Name -> BinOp Source #

Given an operator name, return the operator that determines its syntactical properties.

progImports :: ProgBase f vn -> [(String, SrcLoc)] Source #

The modules imported by a Futhark program.

decImports :: DecBase f vn -> [(String, SrcLoc)] Source #

The modules imported by a single declaration.

progModuleTypes :: Ord vn => ProgBase f vn -> Set vn Source #

The set of module types used in any exported (non-local) declaration.

identifierReference :: String -> Maybe ((String, String, Maybe FilePath), String) Source #

Extract a leading ((name, namespace, file), remainder) from a documentation comment string. These are formatted as `name`@namespace[@file]. Let us hope that this pattern does not occur anywhere else.

identifierReferences :: String -> [(String, String, Maybe FilePath)] Source #

Find all the identifier references in a string.

Queries on expressions

typeOf :: ExpBase Info VName -> PatternType Source #

The type of an Futhark term. The aliasing will refer to itself, if the term is a non-tuple-typed variable.

Queries on patterns and params

patternIdents :: (Functor f, Ord vn) => PatternBase f vn -> Set (IdentBase f vn) Source #

The set of identifiers bound in a pattern.

patternType :: PatternBase Info VName -> PatternType Source #

The type of values bound by the pattern.

patternStructType :: PatternBase Info VName -> StructType Source #

The type matched by the pattern, including shape declarations if present.

patternPatternType :: PatternBase Info VName -> PatternType Source #

The type of a pattern, including shape annotations.

patternParam :: PatternBase Info VName -> (Maybe VName, StructType) Source #

When viewed as a function parameter, does this pattern correspond to a named parameter of some type?

patternNoShapeAnnotations :: PatternBase Info VName -> PatternBase Info VName Source #

Remove all shape annotations from a pattern, leaving them unnamed instead.

patternOrderZero :: PatternBase Info vn -> Bool Source #

patternOrderZero pat is True if all of the types in the given pattern have order 0.

patternDimNames :: PatternBase Info VName -> Set VName Source #

Extract all the shape names that occur in a given pattern.

Queries on types

uniqueness :: TypeBase shape as -> Uniqueness Source #

Return the uniqueness of a type.

unique :: TypeBase shape as -> Bool Source #

unique t is True if the type of the argument is unique.

aliases :: Monoid as => TypeBase shape as -> as Source #

Return the set of all variables mentioned in the aliasing of a type.

diet :: TypeBase shape as -> Diet Source #

diet t returns a description of how a function parameter of type t might consume its argument.

arrayRank :: TypeBase dim as -> Int Source #

Return the dimensionality of a type. For non-arrays, this is zero. For a one-dimensional array it is one, for a two-dimensional it is two, and so forth.

nestedDims :: TypeBase (DimDecl VName) as -> [DimDecl VName] Source #

Return any shape declarations in the type, with duplicates removed.

orderZero :: TypeBase dim as -> Bool Source #

orderZero t is True if the argument type has order 0, i.e., it is not a function type, does not contain a function type as a subcomponent, and may not be instantiated with a function type.

unfoldFunType :: TypeBase dim as -> ([TypeBase dim as], TypeBase dim as) Source #

Extract the parameter types and return type from a type. If the type is not an arrow type, the list of parameter types is empty.

foldFunType :: Monoid as => [TypeBase dim as] -> TypeBase dim as -> TypeBase dim as Source #

typeVars :: Monoid as => TypeBase dim as -> Set VName Source #

The type names mentioned in a type.

typeDimNames :: TypeBase (DimDecl VName) als -> Set VName Source #

Extract all the shape names that occur in a given type.

Operations on types

rank :: Int -> ShapeDecl () Source #

Construct a ShapeDecl with the given number of zero-information dimensions.

peelArray :: Int -> TypeBase dim as -> Maybe (TypeBase dim as) Source #

peelArray n t returns the type resulting from peeling the first n array dimensions from t. Returns Nothing if t has less than n dimensions.

stripArray :: Monoid as => Int -> TypeBase dim as -> TypeBase dim as Source #

stripArray n t removes the n outermost layers of the array. Essentially, it is the type of indexing an array of type t with n indexes.

arrayOf :: Monoid as => TypeBase dim as -> ShapeDecl dim -> Uniqueness -> Maybe (TypeBase dim as) Source #

arrayOf t s u constructs an array type. The convenience compared to using the Array constructor directly is that t can itself be an array. If t is an n-dimensional array, and s is a list of length n, the resulting type is of an n+m dimensions. The uniqueness of the new array will be u, no matter the uniqueness of t. The function returns Nothing in case an attempt is made to create an array of functions.

toStructural :: TypeBase dim as -> TypeBase () () Source #

Convert any type to one that has rank information, no alias information, and no embedded names.

toStruct :: TypeBase dim as -> TypeBase dim () Source #

Remove aliasing information from a type.

fromStruct :: TypeBase dim as -> TypeBase dim Aliasing Source #

Replace no aliasing with an empty alias set.

setAliases :: TypeBase dim asf -> ast -> TypeBase dim ast Source #

t `setAliases` als returns t, but with als substituted for any already present aliasing.

addAliases :: TypeBase dim asf -> (asf -> ast) -> TypeBase dim ast Source #

t `addAliases` f returns t, but with any already present aliasing replaced by f applied to that aliasing.

setUniqueness :: TypeBase dim as -> Uniqueness -> TypeBase dim as Source #

Set the uniqueness attribute of a type. If the type is a tuple, the uniqueness of its components will be modified.

removeShapeAnnotations :: TypeBase (DimDecl vn) as -> TypeBase () as Source #

Change the shape of a type to be just the Rank.

vacuousShapeAnnotations :: TypeBase () as -> TypeBase (DimDecl vn) as Source #

Add size annotations that are all AnyDim.

anyDimShapeAnnotations :: TypeBase (DimDecl vn) as -> TypeBase (DimDecl vn) as Source #

Change all size annotations to be AnyDim.

tupleRecord :: [TypeBase dim as] -> TypeBase dim as Source #

Create a record type corresponding to a tuple with the given element types.

tupleFieldNames :: [Name] Source #

Increasing field names for a tuple (starts at 1).

sortFields :: Map Name a -> [(Name, a)] Source #

Sort fields by their name; taking care to sort numeric fields by their numeric value. This ensures that tuples and tuple-like records match.

combineTypeShapes :: (Monoid as, ArrayDim dim) => TypeBase dim as -> TypeBase dim as -> TypeBase dim as Source #

Combine the shape information of types as much as possible. The first argument is the orignal type and the second is the type of the transformed expression. This is necessary since the original type may contain additional information (e.g., shape restrictions) from the user given annotation.

unscopeType :: Set VName -> PatternType -> PatternType Source #

The type is leaving a scope, so clean up any aliases that reference the bound variables, and turn any dimensions that name them into AnyDim instead.

Values of these types are produces by the parser. They use unadorned names and have no type information, apart from that which is syntactically required.

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 #

type UncheckedType = TypeBase (ShapeDecl Name) () Source #

A type with no aliasing information but shape annotations.

type UncheckedArrayElemType = ArrayElemTypeBase (ShapeDecl Name) Source #

An array element type with no aliasing information.

type UncheckedIdent = IdentBase NoInfo Name Source #

An identifier with no type annotations.

type UncheckedTypeDecl = TypeDeclBase NoInfo Name Source #

A type declaration with no expanded type.

type UncheckedDimIndex = DimIndexBase NoInfo Name Source #

An index with no type annotations.

type UncheckedExp = ExpBase NoInfo Name Source #

An expression with no type annotations.

type UncheckedModExp = ModExpBase NoInfo Name Source #

A module expression with no type annotations.

type UncheckedSigExp = SigExpBase NoInfo Name Source #

A module type expression with no type annotations.

type UncheckedTypeParam = TypeParamBase Name Source #

A type parameter with no type annotations.

type UncheckedPattern = PatternBase NoInfo Name Source #

A pattern with no type annotations.

type UncheckedValBind = ValBindBase NoInfo Name Source #

A function declaration with no type annotations.

type UncheckedDec = DecBase NoInfo Name Source #

A declaration with no type annotations.

type UncheckedProg = ProgBase NoInfo Name Source #

A Futhark program with no type annotations.

type UncheckedCase = CaseBase NoInfo Name Source #

A case (of a match expression) with no type annotations.