| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Futhark.Analysis.PrimExp
Description
A primitive expression is an expression where the non-leaves are primitive operators. Our representation does not guarantee that the expression is type-correct.
Synopsis
- data PrimExp v
- evalPrimExp :: (Pretty v, MonadFail m) => (v -> m PrimValue) -> PrimExp v -> m PrimValue
- primExpType :: PrimExp v -> PrimType
- primExpSizeAtLeast :: Int -> PrimExp v -> Bool
- coerceIntPrimExp :: IntType -> PrimExp v -> PrimExp v
- leafExpTypes :: Ord a => PrimExp a -> Set (a, PrimType)
- true :: PrimExp v
- false :: PrimExp v
- constFoldPrimExp :: PrimExp v -> PrimExp v
- module Futhark.Representation.Primitive
- (.&&.) :: PrimExp v -> PrimExp v -> PrimExp v
- (.||.) :: PrimExp v -> PrimExp v -> PrimExp v
- (.<.) :: PrimExp v -> PrimExp v -> PrimExp v
- (.<=.) :: PrimExp v -> PrimExp v -> PrimExp v
- (.>.) :: PrimExp v -> PrimExp v -> PrimExp v
- (.>=.) :: PrimExp v -> PrimExp v -> PrimExp v
- (.==.) :: PrimExp v -> PrimExp v -> PrimExp v
- (.&.) :: PrimExp v -> PrimExp v -> PrimExp v
- (.|.) :: PrimExp v -> PrimExp v -> PrimExp v
- (.^.) :: PrimExp v -> PrimExp v -> PrimExp v
Documentation
A primitive expression parametrised over the representation of
free variables. Note that the Functor, Traversable, and Num
instances perform automatic (but simple) constant folding.
Note also that the Num instance assumes OverflowUndef
semantics!
Constructors
| LeafExp v PrimType | |
| ValueExp PrimValue | |
| BinOpExp BinOp (PrimExp v) (PrimExp v) | |
| CmpOpExp CmpOp (PrimExp v) (PrimExp v) | |
| UnOpExp UnOp (PrimExp v) | |
| ConvOpExp ConvOp (PrimExp v) | |
| FunExp String [PrimExp v] PrimType |
Instances
primExpType :: PrimExp v -> PrimType Source #
constFoldPrimExp :: PrimExp v -> PrimExp v Source #
Perform quick and dirty constant folding on the top level of a PrimExp. This is necessary because we want to consider e.g. equality modulo constant folding.
(.<.) :: PrimExp v -> PrimExp v -> PrimExp v infix 4 Source #
Lifted relational operators; assuming signed numbers in case of integers.
(.<=.) :: PrimExp v -> PrimExp v -> PrimExp v infix 4 Source #
Lifted relational operators; assuming signed numbers in case of integers.
(.>.) :: PrimExp v -> PrimExp v -> PrimExp v infix 4 Source #
Lifted relational operators; assuming signed numbers in case of integers.
(.>=.) :: PrimExp v -> PrimExp v -> PrimExp v infix 4 Source #
Lifted relational operators; assuming signed numbers in case of integers.