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

Safe HaskellNone
LanguageHaskell2010

Futhark.Representation.Primitive

Contents

Description

Definitions of primitive types, the values that inhabit these types, and operations on these values. A primitive value can also be called a scalar.

Essentially, this module describes the subset of the (internal) Futhark language that operates on primitive types.

Synopsis

Types

data IntType Source #

An integer type, ordered by size. Note that signedness is not a property of the type, but a property of the operations performed on values of these types.

Constructors

Int8 
Int16 
Int32 
Int64 

allIntTypes :: [IntType] Source #

A list of all integer types.

data FloatType Source #

A floating point type.

Constructors

Float32 
Float64 
Instances
Bounded FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Enum FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Eq FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Ord FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Show FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Pretty FloatType Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: FloatType -> Doc #

pprPrec :: Int -> FloatType -> Doc #

pprList :: [FloatType] -> Doc #

allFloatTypes :: [FloatType] Source #

A list of all floating-point types.

data PrimType Source #

Low-level primitive types.

allPrimTypes :: [PrimType] Source #

A list of all primitive types.

Values

intValue :: Integral int => IntType -> int -> IntValue Source #

Create an IntValue from a type and an Integer.

valueIntegral :: Integral int => IntValue -> int Source #

Convert an IntValue to any Integral type.

floatValue :: Real num => FloatType -> num -> FloatValue Source #

Create a FloatValue from a type and a Rational.

primValueType :: PrimValue -> PrimType Source #

The type of a basic value.

blankPrimValue :: PrimType -> PrimValue Source #

A "blank" value of the given primitive type - this is zero, or whatever is close to it. Don't depend on this value, but use it for e.g. creating arrays to be populated by do-loops.

Operations

data UnOp Source #

Various unary operators. It is a bit ad-hoc what is a unary operator and what is a built-in function. Perhaps these should all go away eventually.

Constructors

Not

E.g., ! True == False.

Complement IntType

E.g., ~(~1) = 1.

Abs IntType

abs(-2) = 2.

FAbs FloatType

fabs(-2.0) = 2.0.

SSignum IntType

Signed sign function: ssignum(-2) = -1.

USignum IntType

Unsigned sign function: usignum(2) = 1.

Instances
Eq UnOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

(==) :: UnOp -> UnOp -> Bool #

(/=) :: UnOp -> UnOp -> Bool #

Ord UnOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

compare :: UnOp -> UnOp -> Ordering #

(<) :: UnOp -> UnOp -> Bool #

(<=) :: UnOp -> UnOp -> Bool #

(>) :: UnOp -> UnOp -> Bool #

(>=) :: UnOp -> UnOp -> Bool #

max :: UnOp -> UnOp -> UnOp #

min :: UnOp -> UnOp -> UnOp #

Show UnOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

showsPrec :: Int -> UnOp -> ShowS #

show :: UnOp -> String #

showList :: [UnOp] -> ShowS #

Pretty UnOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: UnOp -> Doc #

pprPrec :: Int -> UnOp -> Doc #

pprList :: [UnOp] -> Doc #

allUnOps :: [UnOp] Source #

A list of all unary operators for all types.

data BinOp Source #

Binary operators. These correspond closely to the binary operators in LLVM. Most are parametrised by their expected input and output types.

Constructors

Add IntType

Integer addition.

FAdd FloatType

Floating-point addition.

Sub IntType

Integer subtraction.

FSub FloatType

Floating-point subtraction.

Mul IntType

Integer multiplication.

FMul FloatType

Floating-point multiplication.

UDiv IntType

Unsigned integer division. Rounds towards negativity infinity. Note: this is different from LLVM.

SDiv IntType

Signed integer division. Rounds towards negativity infinity. Note: this is different from LLVM.

FDiv FloatType

Floating-point division.

UMod IntType

Unsigned integer modulus; the countepart to UDiv.

SMod IntType

Signed integer modulus; the countepart to SDiv.

SQuot IntType

Signed integer division. Rounds towards zero. This corresponds to the sdiv instruction in LLVM.

SRem IntType

Signed integer division. Rounds towards zero. This corresponds to the srem instruction in LLVM.

SMin IntType

Returns the smallest of two signed integers.

UMin IntType

Returns the smallest of two unsigned integers.

FMin FloatType

Returns the smallest of two floating-point numbers.

SMax IntType

Returns the greatest of two signed integers.

UMax IntType

Returns the greatest of two unsigned integers.

FMax FloatType

Returns the greatest of two floating-point numbers.

Shl IntType

Left-shift.

LShr IntType

Logical right-shift, zero-extended.

AShr IntType

Arithmetic right-shift, sign-extended.

And IntType

Bitwise and.

Or IntType

Bitwise or.

Xor IntType

Bitwise exclusive-or.

Pow IntType

Integer exponentiation.

FPow FloatType

Floating-point exponentiation.

LogAnd

Boolean and - not short-circuiting.

LogOr

Boolean or - not short-circuiting.

Instances
Eq BinOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

(==) :: BinOp -> BinOp -> Bool #

(/=) :: BinOp -> BinOp -> Bool #

Ord BinOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

compare :: BinOp -> BinOp -> Ordering #

(<) :: BinOp -> BinOp -> Bool #

(<=) :: BinOp -> BinOp -> Bool #

(>) :: BinOp -> BinOp -> Bool #

(>=) :: BinOp -> BinOp -> Bool #

max :: BinOp -> BinOp -> BinOp #

min :: BinOp -> BinOp -> BinOp #

Show BinOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

Pretty BinOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: BinOp -> Doc #

pprPrec :: Int -> BinOp -> Doc #

pprList :: [BinOp] -> Doc #

allBinOps :: [BinOp] Source #

A list of all binary operators for all types.

data ConvOp Source #

Conversion operators try to generalise the from t0 x to t1 instructions from LLVM.

Constructors

ZExt IntType IntType

Zero-extend the former integer type to the latter. If the new type is smaller, the result is a truncation.

SExt IntType IntType

Sign-extend the former integer type to the latter. If the new type is smaller, the result is a truncation.

FPConv FloatType FloatType

Convert value of the former floating-point type to the latter. If the new type is smaller, the result is a truncation.

FPToUI FloatType IntType

Convert a floating-point value to the nearest unsigned integer (rounding towards zero).

FPToSI FloatType IntType

Convert a floating-point value to the nearest signed integer (rounding towards zero).

UIToFP IntType FloatType

Convert an unsigned integer to a floating-point value.

SIToFP IntType FloatType

Convert a signed integer to a floating-point value.

IToB IntType

Convert an integer to a boolean value. Zero becomes false; anything else is true.

BToI IntType

Convert a boolean to an integer. True is converted to 1 and False to 0.

Instances
Eq ConvOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

(==) :: ConvOp -> ConvOp -> Bool #

(/=) :: ConvOp -> ConvOp -> Bool #

Ord ConvOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Show ConvOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Pretty ConvOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: ConvOp -> Doc #

pprPrec :: Int -> ConvOp -> Doc #

pprList :: [ConvOp] -> Doc #

allConvOps :: [ConvOp] Source #

A list of all conversion operators for all types.

data CmpOp Source #

Comparison operators are like BinOps, but they return PrimTypes. The somewhat ugly constructor names are straight out of LLVM.

Constructors

CmpEq PrimType

All types equality.

CmpUlt IntType

Unsigned less than.

CmpUle IntType

Unsigned less than or equal.

CmpSlt IntType

Signed less than.

CmpSle IntType

Signed less than or equal.

FCmpLt FloatType

Floating-point less than.

FCmpLe FloatType

Floating-point less than or equal.

CmpLlt

Boolean less than.

CmpLle

Boolean less than or equal.

Instances
Eq CmpOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

(==) :: CmpOp -> CmpOp -> Bool #

(/=) :: CmpOp -> CmpOp -> Bool #

Ord CmpOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

compare :: CmpOp -> CmpOp -> Ordering #

(<) :: CmpOp -> CmpOp -> Bool #

(<=) :: CmpOp -> CmpOp -> Bool #

(>) :: CmpOp -> CmpOp -> Bool #

(>=) :: CmpOp -> CmpOp -> Bool #

max :: CmpOp -> CmpOp -> CmpOp #

min :: CmpOp -> CmpOp -> CmpOp #

Show CmpOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

showsPrec :: Int -> CmpOp -> ShowS #

show :: CmpOp -> String #

showList :: [CmpOp] -> ShowS #

Pretty CmpOp Source # 
Instance details

Defined in Futhark.Representation.Primitive

Methods

ppr :: CmpOp -> Doc #

pprPrec :: Int -> CmpOp -> Doc #

pprList :: [CmpOp] -> Doc #

allCmpOps :: [CmpOp] Source #

A list of all comparison operators for all types.

Unary Operations

doComplement :: IntValue -> IntValue Source #

E.g., ~(~1) = 1.

doAbs :: IntValue -> IntValue Source #

abs(-2) = 2.

doFAbs :: FloatValue -> FloatValue Source #

abs(-2.0) = 2.0.

doSSignum :: IntValue -> IntValue Source #

ssignum(-2) = -1.

doUSignum :: IntValue -> IntValue Source #

usignum(-2) = -1.

Binary Operations

doAdd :: IntValue -> IntValue -> IntValue Source #

Integer addition.

doMul :: IntValue -> IntValue -> IntValue Source #

Integer multiplication.

doSDiv :: IntValue -> IntValue -> Maybe IntValue Source #

Signed integer division. Rounds towards negativity infinity. Note: this is different from LLVM.

doSMod :: IntValue -> IntValue -> Maybe IntValue Source #

Signed integer modulus; the countepart to SDiv.

doPow :: IntValue -> IntValue -> Maybe IntValue Source #

Signed integer exponentatation.

Conversion Operations

doZExt :: IntValue -> IntType -> IntValue Source #

Zero-extend the given integer value to the size of the given type. If the type is smaller than the given value, the result is a truncation.

doSExt :: IntValue -> IntType -> IntValue Source #

Sign-extend the given integer value to the size of the given type. If the type is smaller than the given value, the result is a truncation.

doFPConv :: FloatValue -> FloatType -> FloatValue Source #

Convert the former floating-point type to the latter.

doFPToUI :: FloatValue -> IntType -> IntValue Source #

Convert a floating-point value to the nearest unsigned integer (rounding towards zero).

doFPToSI :: FloatValue -> IntType -> IntValue Source #

Convert a floating-point value to the nearest signed integer (rounding towards zero).

doUIToFP :: IntValue -> FloatType -> FloatValue Source #

Convert an unsigned integer to a floating-point value.

doSIToFP :: IntValue -> FloatType -> FloatValue Source #

Convert a signed integer to a floating-point value.

intToInt64 :: IntValue -> Int64 Source #

Translate an IntValue to IntType. This is guaranteed to fit.

intToWord64 :: IntValue -> Word64 Source #

Translate an IntValue to Word64. This is guaranteed to fit.

Comparison Operations

doCmpEq :: PrimValue -> PrimValue -> Bool Source #

Compare any two primtive values for exact equality.

doCmpUlt :: IntValue -> IntValue -> Bool Source #

Unsigned less than.

doCmpUle :: IntValue -> IntValue -> Bool Source #

Unsigned less than or equal.

doCmpSlt :: IntValue -> IntValue -> Bool Source #

Signed less than.

doCmpSle :: IntValue -> IntValue -> Bool Source #

Signed less than or equal.

doFCmpLt :: FloatValue -> FloatValue -> Bool Source #

Floating-point less than.

doFCmpLe :: FloatValue -> FloatValue -> Bool Source #

Floating-point less than or equal.

Type Of

binOpType :: BinOp -> PrimType Source #

The result type of a binary operator.

unOpType :: UnOp -> PrimType Source #

The operand and result type of a unary operator.

cmpOpType :: CmpOp -> PrimType Source #

The operand types of a comparison operator.

convOpType :: ConvOp -> (PrimType, PrimType) Source #

The input and output types of a conversion operator.

Primitive functions

primFuns :: Map String ([PrimType], PrimType, [PrimValue] -> Maybe PrimValue) Source #

A mapping from names of primitive functions to their parameter types, their result type, and a function for evaluating them.

Utility

zeroIsh :: PrimValue -> Bool Source #

Is the given value kind of zero?

oneIsh :: PrimValue -> Bool Source #

Is the given value kind of one?

negativeIsh :: PrimValue -> Bool Source #

Is the given value kind of negative?

primBitSize :: PrimType -> Int Source #

The size of a value of a given primitive type in bites.

primByteSize :: Num a => PrimType -> a Source #

The size of a value of a given primitive type in eight-bit bytes.

intByteSize :: Num a => IntType -> a Source #

The size of a value of a given integer type in eight-bit bytes.

floatByteSize :: Num a => FloatType -> a Source #

The size of a value of a given floating-point type in eight-bit bytes.

commutativeBinOp :: BinOp -> Bool Source #

True if the given binary operator is commutative.

Prettyprinting

prettySigned :: Bool -> PrimType -> String Source #

True if signed. Only makes a difference for integer types.