Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides facilities for obtaining the types of
various Futhark constructs. Typically, you will need to execute
these in a context where type information is available as a
Scope
; usually by using a monad that is an instance of
HasScope
. The information is returned as a list of ExtType
values - one for each of the values the Futhark construct returns.
Some constructs (such as subexpressions) can produce only a single
value, and their typing functions hence do not return a list.
Some representations may have more specialised facilities enabling even more information - for example, Futhark.Representation.ExplicitMemory exposes functionality for also obtaining information about the storage location of results.
Synopsis
- expExtType :: (HasScope lore m, TypedOp (Op lore)) => Exp lore -> m [ExtType]
- expExtTypeSize :: (Annotations lore, TypedOp (Op lore)) => Exp lore -> Int
- subExpType :: HasScope t m => SubExp -> m Type
- bodyExtType :: (HasScope lore m, Monad m) => Body lore -> m [ExtType]
- primOpType :: HasScope t m => BasicOp lore -> m [Type]
- mapType :: SubExp -> Lambda lore -> [Type]
- subExpShapeContext :: HasScope t m => [TypeBase ExtShape u] -> [SubExp] -> m [SubExp]
- loopResultContext :: FreeIn attr => [Param attr] -> [Param attr] -> [Param attr]
- loopExtType :: [Ident] -> [Ident] -> [ExtType]
- module Futhark.Representation.AST.RetType
- module Futhark.Representation.AST.Attributes.Scope
- class TypedOp op where
Documentation
expExtType :: (HasScope lore m, TypedOp (Op lore)) => Exp lore -> m [ExtType] Source #
The type of an expression.
expExtTypeSize :: (Annotations lore, TypedOp (Op lore)) => Exp lore -> Int Source #
The number of values returned by an expression.
bodyExtType :: (HasScope lore m, Monad m) => Body lore -> m [ExtType] Source #
The type of a body. Watch out: this only works for the degenerate case where the body does not already return its context.
mapType :: SubExp -> Lambda lore -> [Type] Source #
mapType f arrts
wraps each element in the return type of f
in
an array with size equal to the outermost dimension of the first
element of arrts
.
subExpShapeContext :: HasScope t m => [TypeBase ExtShape u] -> [SubExp] -> m [SubExp] Source #
Given the return type of a function and the subexpressions returned by that function, return the size context.
loopResultContext :: FreeIn attr => [Param attr] -> [Param attr] -> [Param attr] Source #
A loop returns not only its value merge parameters, but may also
have an existential context. Thus, loopResult ctxmergeparams
valmergeparams
returns those paramters in ctxmergeparams
that
constitute the returned context.
loopExtType :: [Ident] -> [Ident] -> [ExtType] Source #
Given the context and value merge parameters of a Futhark loop
,
produce the return type.
Return type
Type environment
Extensibility
class TypedOp op where Source #
Any operation must define an instance of this class, which describes the type of the operation (at the value level).