futhark-0.16.4: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

Documentation

data PrimExp v Source #

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!

Instances

Instances details
Functor PrimExp Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

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

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

Foldable PrimExp Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> PrimExp a -> m #

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

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

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

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

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

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

toList :: PrimExp a -> [a] #

null :: PrimExp a -> Bool #

length :: PrimExp a -> Int #

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

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

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

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

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

Traversable PrimExp Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

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

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

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

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

Eq v => Eq (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

(==) :: PrimExp v -> PrimExp v -> Bool #

(/=) :: PrimExp v -> PrimExp v -> Bool #

Pretty v => Fractional (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

(/) :: PrimExp v -> PrimExp v -> PrimExp v #

recip :: PrimExp v -> PrimExp v #

fromRational :: Rational -> PrimExp v #

Pretty v => Num (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

(+) :: PrimExp v -> PrimExp v -> PrimExp v #

(-) :: PrimExp v -> PrimExp v -> PrimExp v #

(*) :: PrimExp v -> PrimExp v -> PrimExp v #

negate :: PrimExp v -> PrimExp v #

abs :: PrimExp v -> PrimExp v #

signum :: PrimExp v -> PrimExp v #

fromInteger :: Integer -> PrimExp v #

Ord v => Ord (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

compare :: PrimExp v -> PrimExp v -> Ordering #

(<) :: PrimExp v -> PrimExp v -> Bool #

(<=) :: PrimExp v -> PrimExp v -> Bool #

(>) :: PrimExp v -> PrimExp v -> Bool #

(>=) :: PrimExp v -> PrimExp v -> Bool #

max :: PrimExp v -> PrimExp v -> PrimExp v #

min :: PrimExp v -> PrimExp v -> PrimExp v #

Show v => Show (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

showsPrec :: Int -> PrimExp v -> ShowS #

show :: PrimExp v -> String #

showList :: [PrimExp v] -> ShowS #

Pretty v => Pretty (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

ppr :: PrimExp v -> Doc #

pprPrec :: Int -> PrimExp v -> Doc #

pprList :: [PrimExp v] -> Doc #

Pretty v => IntegralExp (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

FreeIn v => FreeIn (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp

Methods

freeIn' :: PrimExp v -> FV Source #

Substitute v => Substitute (PrimExp v) Source # 
Instance details

Defined in Futhark.Transform.Substitute

ToExp v => ToExp (PrimExp v) Source # 
Instance details

Defined in Futhark.Analysis.PrimExp.Convert

Methods

toExp :: MonadBinder m => PrimExp v -> m (Exp (Lore m)) Source #

ToExp (PrimExp VName) Source # 
Instance details

Defined in Futhark.CodeGen.ImpGen

evalPrimExp :: (Pretty v, MonadFail m) => (v -> m PrimValue) -> PrimExp v -> m PrimValue Source #

Evaluate a PrimExp in the given monad. Invokes fail on type errors.

primExpType :: PrimExp v -> PrimType Source #

The type of values returned by a PrimExp. This function returning does not imply that the PrimExp is type-correct.

primExpSizeAtLeast :: Int -> PrimExp v -> Bool Source #

True if the PrimExp has at least this many nodes. This can be much more efficient than comparing with length for large PrimExps, as this function is lazy.

coerceIntPrimExp :: IntType -> PrimExp v -> PrimExp v Source #

If the given PrimExp is a constant of the wrong integer type, coerce it to the given integer type. This is a workaround for an issue in the Num instance.

leafExpTypes :: Ord a => PrimExp a -> Set (a, PrimType) Source #

Produce a mapping from the leaves of the PrimExp to their designated types.

true :: PrimExp v Source #

Boolean-valued PrimExps.

false :: PrimExp v Source #

Boolean-valued PrimExps.

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.

sExt :: IntType -> PrimExp v -> PrimExp v Source #

Smart constructor for sign extension that does a bit of constant folding.

zExt :: IntType -> PrimExp v -> PrimExp v Source #

Smart constructor for zero extension that does a bit of constant folding.

(.&&.) :: PrimExp v -> PrimExp v -> PrimExp v infixr 3 Source #

Lifted logical conjunction.

(.||.) :: PrimExp v -> PrimExp v -> PrimExp v infixr 2 Source #

Lifted logical conjunction.

(.<.) :: 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.

(.==.) :: 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 Source #

Lifted bitwise operators.

(.|.) :: PrimExp v -> PrimExp v -> PrimExp v Source #

Lifted bitwise operators.

(.^.) :: PrimExp v -> PrimExp v -> PrimExp v Source #

Lifted bitwise operators.