Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- data Intrinsic
- intrinsics :: Map VName Intrinsic
- maxIntrinsicTag :: Int
- namesToPrimTypes :: Map Name PrimType
- qualName :: v -> QualName v
- qualify :: v -> QualName v -> QualName v
- typeName :: VName -> TypeName
- valueType :: Value -> ValueType
- primValueType :: PrimValue -> PrimType
- leadingOperator :: Name -> BinOp
- progImports :: ProgBase f vn -> [(String, SrcLoc)]
- decImports :: DecBase f vn -> [(String, SrcLoc)]
- progModuleTypes :: Ord vn => ProgBase f vn -> Set vn
- identifierReference :: String -> Maybe ((String, String, Maybe FilePath), String)
- prettyStacktrace :: Int -> [String] -> String
- typeOf :: ExpBase Info VName -> PatternType
- valBindTypeScheme :: ValBindBase Info VName -> ([TypeParamBase VName], StructType)
- funType :: [PatternBase Info VName] -> StructType -> StructType
- patternIdents :: (Functor f, Ord vn) => PatternBase f vn -> Set (IdentBase f vn)
- patternNames :: (Functor f, Ord vn) => PatternBase f vn -> Set vn
- patternMap :: Functor f => PatternBase f VName -> Map VName (IdentBase f VName)
- patternType :: PatternBase Info VName -> PatternType
- patternStructType :: PatternBase Info VName -> StructType
- patternParam :: PatternBase Info VName -> (PName, StructType)
- patternOrderZero :: PatternBase Info vn -> Bool
- patternDimNames :: PatternBase Info VName -> Set VName
- uniqueness :: TypeBase shape as -> Uniqueness
- unique :: TypeBase shape as -> Bool
- aliases :: Monoid as => TypeBase shape as -> as
- diet :: TypeBase shape as -> Diet
- arrayRank :: TypeBase dim as -> Int
- arrayShape :: TypeBase dim as -> ShapeDecl dim
- nestedDims :: TypeBase (DimDecl VName) as -> [DimDecl VName]
- orderZero :: TypeBase dim as -> Bool
- unfoldFunType :: TypeBase dim as -> ([TypeBase dim as], TypeBase dim as)
- foldFunType :: Monoid as => [TypeBase dim as] -> TypeBase dim as -> TypeBase dim as
- typeVars :: Monoid as => TypeBase dim as -> Set VName
- typeDimNames :: TypeBase (DimDecl VName) als -> Set VName
- primByteSize :: Num a => PrimType -> a
- rank :: Int -> ShapeDecl (DimDecl VName)
- peelArray :: Int -> TypeBase dim as -> Maybe (TypeBase dim as)
- stripArray :: Int -> TypeBase dim as -> TypeBase dim as
- arrayOf :: Monoid as => TypeBase dim as -> ShapeDecl dim -> Uniqueness -> TypeBase dim as
- toStructural :: TypeBase dim as -> TypeBase () ()
- toStruct :: TypeBase dim as -> TypeBase dim ()
- fromStruct :: TypeBase dim as -> TypeBase dim Aliasing
- setAliases :: TypeBase dim asf -> ast -> TypeBase dim ast
- addAliases :: TypeBase dim asf -> (asf -> ast) -> TypeBase dim ast
- setUniqueness :: TypeBase dim as -> Uniqueness -> TypeBase dim as
- noSizes :: TypeBase (DimDecl vn) as -> TypeBase () as
- anySizes :: TypeBase (DimDecl vn) as -> TypeBase (DimDecl vn) as
- traverseDims :: forall f fdim tdim als. Applicative f => (Set VName -> DimPos -> fdim -> f tdim) -> TypeBase fdim als -> f (TypeBase tdim als)
- data DimPos
- mustBeExplicit :: StructType -> Set VName
- mustBeExplicitInType :: StructType -> Set VName
- tupleRecord :: [TypeBase dim as] -> TypeBase dim as
- isTupleRecord :: TypeBase dim as -> Maybe [TypeBase dim as]
- areTupleFields :: Map Name a -> Maybe [a]
- tupleFields :: [a] -> Map Name a
- tupleFieldNames :: [Name]
- sortFields :: Map Name a -> [(Name, a)]
- sortConstrs :: Map Name a -> [(Name, a)]
- isTypeParam :: TypeParamBase vn -> Bool
- isSizeParam :: TypeParamBase vn -> Bool
- combineTypeShapes :: (Monoid as, ArrayDim dim) => TypeBase dim as -> TypeBase dim as -> TypeBase dim as
- matchDims :: (Monoid as, Monad m) => (d1 -> d2 -> m d1) -> TypeBase d1 as -> TypeBase d2 as -> m (TypeBase d1 as)
- unscopeType :: Set VName -> PatternType -> PatternType
- onRecordField :: (TypeBase dim als -> TypeBase dim als) -> [Name] -> TypeBase dim als -> Maybe (TypeBase dim als)
- data NoInfo a = NoInfo
- type UncheckedType = TypeBase (ShapeDecl Name) ()
- type UncheckedTypeExp = TypeExp Name
- type UncheckedIdent = IdentBase NoInfo Name
- type UncheckedTypeDecl = TypeDeclBase NoInfo Name
- type UncheckedDimIndex = DimIndexBase NoInfo Name
- type UncheckedExp = ExpBase NoInfo Name
- type UncheckedModExp = ModExpBase NoInfo Name
- type UncheckedSigExp = SigExpBase NoInfo Name
- type UncheckedTypeParam = TypeParamBase Name
- type UncheckedPattern = PatternBase NoInfo Name
- type UncheckedValBind = ValBindBase NoInfo Name
- type UncheckedDec = DecBase NoInfo Name
- type UncheckedSpec = SpecBase NoInfo Name
- type UncheckedProg = ProgBase NoInfo Name
- type UncheckedCase = CaseBase NoInfo Name
Various
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.
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.
qualify :: v -> QualName v -> QualName v Source #
Add another qualifier (at the head) to a qualified name.
primValueType :: PrimValue -> PrimType Source #
The type of a basic value.
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.
prettyStacktrace :: Int -> [String] -> String Source #
Given a list of strings representing entries in the stack trace and the index of the frame to highlight, produce a final newline-terminated string for showing to the user. This string should also be preceded by a newline. The most recent stack frame must come first in the list.
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.
valBindTypeScheme :: ValBindBase Info VName -> ([TypeParamBase VName], StructType) Source #
The type scheme of a value binding, comprising the type parameters and the actual type.
funType :: [PatternBase Info VName] -> StructType -> StructType Source #
The type of a function with the given parameters and return type.
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.
patternNames :: (Functor f, Ord vn) => PatternBase f vn -> Set vn Source #
The set of names bound in a pattern.
patternMap :: Functor f => PatternBase f VName -> Map VName (IdentBase f VName) Source #
A mapping from names bound in a map to their identifier.
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.
patternParam :: PatternBase Info VName -> (PName, StructType) Source #
When viewed as a function parameter, does this pattern correspond to a named parameter of some type?
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.
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.
arrayShape :: TypeBase dim as -> ShapeDecl dim Source #
Return the shape of a type - for non-arrays, this is mempty
.
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 #
foldFunType ts ret
creates a function type (Arrow
) that takes
ts
as parameters and returns ret
.
typeDimNames :: TypeBase (DimDecl VName) als -> Set VName Source #
Extract all the shape names that occur in a given type.
primByteSize :: Num a => PrimType -> a Source #
The size of values of this type, in bytes.
Operations on types
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 :: 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 -> 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
.
toStructural :: TypeBase dim as -> TypeBase () () Source #
Convert any type to one that has rank information, no alias information, and no embedded names.
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 record or sum type, the uniqueness of its components will be modified.
noSizes :: TypeBase (DimDecl vn) as -> TypeBase () as Source #
Change the shape of a type to be just the rank.
anySizes :: TypeBase (DimDecl vn) as -> TypeBase (DimDecl vn) as Source #
Change all size annotations to be AnyDim
.
traverseDims :: forall f fdim tdim als. Applicative f => (Set VName -> DimPos -> fdim -> f tdim) -> TypeBase fdim als -> f (TypeBase tdim als) Source #
Perform a traversal (possibly including replacement) on sizes that are parameters in a function type, but also including the type immediately passed to the function. Also passes along a set of the parameter names inside the type that have come in scope at the occurrence of the dimension.
Where does this dimension occur?
PosImmediate | Immediately in the argument to |
PosParam | In a function parameter type. |
PosReturn | In a function return type. |
mustBeExplicit :: StructType -> Set VName Source #
Figure out which of the sizes in a binding type must be passed explicitly, because their first use is as something else than just an array dimension.
mustBeExplicitInType :: StructType -> Set VName Source #
Figure out which of the sizes in a parameter type must be passed
explicitly, because their first use is as something else than just
an array dimension. mustBeExplicit
is like this function, but
first decomposes into parameter types.
tupleRecord :: [TypeBase dim as] -> TypeBase dim as Source #
Create a record type corresponding to a tuple with the given element types.
isTupleRecord :: TypeBase dim as -> Maybe [TypeBase dim as] Source #
Does this type corespond to a tuple? If so, return the elements of that tuple.
tupleFields :: [a] -> Map Name a Source #
Construct a record map corresponding to a tuple.
tupleFieldNames :: [Name] Source #
Increasing field names for a tuple (starts at 0).
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.
sortConstrs :: Map Name a -> [(Name, a)] Source #
Sort the constructors of a sum type in some well-defined (but not otherwise significant) manner.
isTypeParam :: TypeParamBase vn -> Bool Source #
Is this a TypeParamType
?
isSizeParam :: TypeParamBase vn -> Bool Source #
Is this a TypeParamDim
?
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.
matchDims :: (Monoid as, Monad m) => (d1 -> d2 -> m d1) -> TypeBase d1 as -> TypeBase d2 as -> m (TypeBase d1 as) Source #
Match the dimensions of otherwise assumed-equal types.
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.
onRecordField :: (TypeBase dim als -> TypeBase dim als) -> [Name] -> TypeBase dim als -> Maybe (TypeBase dim als) Source #
Perform some operation on a given record field. Returns
Nothing
if that field does not exist.
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.
No information functor. Usually used for placeholder type- or aliasing information.
Instances
type UncheckedType = TypeBase (ShapeDecl Name) () Source #
A type with no aliasing information but shape annotations.
type UncheckedTypeExp = TypeExp Name Source #
An expression 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 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.