accelerate-1.1.1.0: An embedded language for accelerated array processing

Copyright[2016..2017] Manuel M T Chakravarty Gabriele Keller Trevor L. McDonell
LicenseBSD3
MaintainerTrevor L. McDonell <tmcdonell@cse.unsw.edu.au>
Stabilityexperimental
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell98

Data.Array.Accelerate.Data.Bits

Description

Bitwise operations for signed and unsigned integer expressions.

Synopsis

Documentation

class Eq a => Bits a where Source #

The Bits class defines bitwise operations over integral scalar expression types. As usual, bits are numbered from zero, with zero being the least significant bit.

Minimal complete definition

(.&.), (.|.), xor, complement, (shift | shiftL, shiftR), (rotate | rotateL, rotateR), isSigned, testBit, bit, popCount

Methods

(.&.) :: Exp a -> Exp a -> Exp a infixl 7 Source #

Bitwise "and"

(.|.) :: Exp a -> Exp a -> Exp a infixl 5 Source #

Bitwise "or"

xor :: Exp a -> Exp a -> Exp a infixl 6 Source #

Bitwise "xor"

complement :: Exp a -> Exp a Source #

Reverse all bits in the argument

shift :: Exp a -> Exp Int -> Exp a infixl 8 Source #

shift x i shifts x left by i bits if i is positive, or right by -i bits otherwise. Right shifts perform sign extension on signed number types; i.e. they fill the top bits with 1 if the x is negative and with 0 otherwise.

rotate :: Exp a -> Exp Int -> Exp a infixl 8 Source #

rotate x i rotates x left by i bits if i is positive, or right by -i bits otherwise.

zeroBits :: Exp a Source #

The value with all bits unset

bit :: Exp Int -> Exp a Source #

bit i is a value with the ith bit set and all other bits clear.

setBit :: Exp a -> Exp Int -> Exp a Source #

x `setBit` i is the same as x .|. bit i

clearBit :: Exp a -> Exp Int -> Exp a Source #

x `clearBit` i is the same as x .&. complement (bit i)

complementBit :: Exp a -> Exp Int -> Exp a Source #

x `complementBit` i is the same as x `xor` bit i

testBit :: Exp a -> Exp Int -> Exp Bool Source #

Return True if the nth bit of the argument is 1

isSigned :: Exp a -> Exp Bool Source #

Return True if the argument is a signed type.

shiftL :: Exp a -> Exp Int -> Exp a infixl 8 Source #

Shift the argument left by the specified number of bits (which must be non-negative).

unsafeShiftL :: Exp a -> Exp Int -> Exp a Source #

Shift the argument left by the specified number of bits. The result is undefined for negative shift amounts and shift amounts greater or equal to the finiteBitSize.

shiftR :: Exp a -> Exp Int -> Exp a infixl 8 Source #

Shift the first argument right by the specified number of bits (which must be non-negative).

Right shifts perform sign extension on signed number types; i.e. they fill the top bits with 1 if x is negative and with 0 otherwise.

unsafeShiftR :: Exp a -> Exp Int -> Exp a Source #

Shift the first argument right by the specified number of bits. The result is undefined for negative shift amounts and shift amounts greater or equal to the finiteBitSize.

rotateL :: Exp a -> Exp Int -> Exp a infixl 8 Source #

Rotate the argument left by the specified number of bits (which must be non-negative).

rotateR :: Exp a -> Exp Int -> Exp a infixl 8 Source #

Rotate the argument right by the specified number of bits (which must be non-negative).

popCount :: Exp a -> Exp Int Source #

Return the number of set bits in the argument. This number is known as the population count or the Hamming weight.

Instances

Bits Bool Source # 
Bits Int Source # 
Bits Int8 Source # 
Bits Int16 Source # 
Bits Int32 Source # 
Bits Int64 Source # 
Bits Word Source # 
Bits Word8 Source # 
Bits Word16 Source # 
Bits Word32 Source # 
Bits Word64 Source # 
Bits CShort Source # 
Bits CUShort Source # 
Bits CInt Source # 
Bits CUInt Source # 
Bits CLong Source # 
Bits CULong Source # 
Bits CLLong Source # 
Bits CULLong Source # 

class Bits b => FiniteBits b where Source #

Methods

finiteBitSize :: Exp b -> Exp Int Source #

Return the number of bits in the type of the argument.

countLeadingZeros :: Exp b -> Exp Int Source #

Count the number of zero bits preceding the most significant set bit. This can be used to compute a base-2 logarithm via:

logBase2 x = finiteBitSize x - 1 - countLeadingZeros x

countTrailingZeros :: Exp b -> Exp Int Source #

Count the number of zero bits following the least significant set bit. The related find-first-set operation can be expressed in terms of this as:

findFirstSet x = 1 + countTrailingZeros x

Instances

FiniteBits Bool Source # 
FiniteBits Int Source # 
FiniteBits Int8 Source # 
FiniteBits Int16 Source # 
FiniteBits Int32 Source # 
FiniteBits Int64 Source # 
FiniteBits Word Source # 
FiniteBits Word8 Source # 
FiniteBits Word16 Source # 
FiniteBits Word32 Source # 
FiniteBits Word64 Source # 
FiniteBits CShort Source # 
FiniteBits CUShort Source # 
FiniteBits CInt Source # 
FiniteBits CUInt Source # 
FiniteBits CLong Source # 
FiniteBits CULong Source # 
FiniteBits CLLong Source # 
FiniteBits CULLong Source #