{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
module Data.Array.Accelerate.Data.Bits (
Bits(..),
FiniteBits(..),
) where
import Data.Array.Accelerate.Array.Data
import Data.Array.Accelerate.Language
import Data.Array.Accelerate.Smart
import Data.Array.Accelerate.Sugar.Elt
import Data.Array.Accelerate.Type
import Data.Array.Accelerate.Classes.Eq
import Data.Array.Accelerate.Classes.Ord
import Data.Array.Accelerate.Classes.Integral ()
import Prelude ( (.), ($), undefined, otherwise )
import qualified Data.Bits as B
infixl 8 `shift`, `rotate`, `shiftL`, `shiftR`, `rotateL`, `rotateR`
infixl 7 .&.
infixl 6 `xor`
infixl 5 .|.
class Eq a => Bits a where
{-# MINIMAL (.&.), (.|.), xor, complement,
(shift | (shiftL, shiftR)),
(rotate | (rotateL, rotateR)),
isSigned, testBit, bit, popCount #-}
(.&.) :: Exp a -> Exp a -> Exp a
(.|.) :: Exp a -> Exp a -> Exp a
xor :: Exp a -> Exp a -> Exp a
complement :: Exp a -> Exp a
shift :: Exp a -> Exp Int -> Exp a
shift Exp a
x Exp Int
i
= Exp Bool -> Exp a -> Exp a -> Exp a
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Ord a => Exp a -> Exp a -> Exp Bool
< Exp Int
0) (Exp a
x Exp a -> Exp Int -> Exp a
forall a. Bits a => Exp a -> Exp Int -> Exp a
`shiftR` (-Exp Int
i))
(Exp a -> Exp a) -> Exp a -> Exp a
forall a b. (a -> b) -> a -> b
$ Exp Bool -> Exp a -> Exp a -> Exp a
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Ord a => Exp a -> Exp a -> Exp Bool
> Exp Int
0) (Exp a
x Exp a -> Exp Int -> Exp a
forall a. Bits a => Exp a -> Exp Int -> Exp a
`shiftL` Exp Int
i)
(Exp a -> Exp a) -> Exp a -> Exp a
forall a b. (a -> b) -> a -> b
$ Exp a
x
rotate :: Exp a -> Exp Int -> Exp a
rotate Exp a
x Exp Int
i
= Exp Bool -> Exp a -> Exp a -> Exp a
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Ord a => Exp a -> Exp a -> Exp Bool
< Exp Int
0) (Exp a
x Exp a -> Exp Int -> Exp a
forall a. Bits a => Exp a -> Exp Int -> Exp a
`rotateR` (-Exp Int
i))
(Exp a -> Exp a) -> Exp a -> Exp a
forall a b. (a -> b) -> a -> b
$ Exp Bool -> Exp a -> Exp a -> Exp a
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Ord a => Exp a -> Exp a -> Exp Bool
> Exp Int
0) (Exp a
x Exp a -> Exp Int -> Exp a
forall a. Bits a => Exp a -> Exp Int -> Exp a
`rotateL` Exp Int
i)
(Exp a -> Exp a) -> Exp a -> Exp a
forall a b. (a -> b) -> a -> b
$ Exp a
x
zeroBits :: Exp a
zeroBits = Exp a -> Exp Int -> Exp a
forall a. Bits a => Exp a -> Exp Int -> Exp a
clearBit (Exp Int -> Exp a
forall a. Bits a => Exp Int -> Exp a
bit Exp Int
0) Exp Int
0
bit :: Exp Int -> Exp a
setBit :: Exp a -> Exp Int -> Exp a
setBit Exp a
x Exp Int
i = Exp a
x Exp a -> Exp a -> Exp a
forall a. Bits a => Exp a -> Exp a -> Exp a
.|. Exp Int -> Exp a
forall a. Bits a => Exp Int -> Exp a
bit Exp Int
i
clearBit :: Exp a -> Exp Int -> Exp a
clearBit Exp a
x Exp Int
i = Exp a
x Exp a -> Exp a -> Exp a
forall a. Bits a => Exp a -> Exp a -> Exp a
.&. Exp a -> Exp a
forall a. Bits a => Exp a -> Exp a
complement (Exp Int -> Exp a
forall a. Bits a => Exp Int -> Exp a
bit Exp Int
i)
complementBit :: Exp a -> Exp Int -> Exp a
complementBit Exp a
x Exp Int
i = Exp a
x Exp a -> Exp a -> Exp a
forall a. Bits a => Exp a -> Exp a -> Exp a
`xor` Exp Int -> Exp a
forall a. Bits a => Exp Int -> Exp a
bit Exp Int
i
testBit :: Exp a -> Exp Int -> Exp Bool
isSigned :: Exp a -> Exp Bool
shiftL :: Exp a -> Exp Int -> Exp a
shiftL Exp a
x Exp Int
i = Exp a
x Exp a -> Exp Int -> Exp a
forall a. Bits a => Exp a -> Exp Int -> Exp a
`shift` Exp Int
i
unsafeShiftL :: Exp a -> Exp Int -> Exp a
unsafeShiftL = Exp a -> Exp Int -> Exp a
forall a. Bits a => Exp a -> Exp Int -> Exp a
shiftL
shiftR :: Exp a -> Exp Int -> Exp a
shiftR Exp a
x Exp Int
i = Exp a
x Exp a -> Exp Int -> Exp a
forall a. Bits a => Exp a -> Exp Int -> Exp a
`shift` (-Exp Int
i)
unsafeShiftR :: Exp a -> Exp Int -> Exp a
unsafeShiftR = Exp a -> Exp Int -> Exp a
forall a. Bits a => Exp a -> Exp Int -> Exp a
shiftR
rotateL :: Exp a -> Exp Int -> Exp a
rotateL Exp a
x Exp Int
i = Exp a
x Exp a -> Exp Int -> Exp a
forall a. Bits a => Exp a -> Exp Int -> Exp a
`rotate` Exp Int
i
rotateR :: Exp a -> Exp Int -> Exp a
rotateR Exp a
x Exp Int
i = Exp a
x Exp a -> Exp Int -> Exp a
forall a. Bits a => Exp a -> Exp Int -> Exp a
`rotate` (-Exp Int
i)
popCount :: Exp a -> Exp Int
class Bits b => FiniteBits b where
finiteBitSize :: Exp b -> Exp Int
countLeadingZeros :: Exp b -> Exp Int
countTrailingZeros :: Exp b -> Exp Int
instance Bits Bool where
.&. :: Exp Bool -> Exp Bool -> Exp Bool
(.&.) = Exp Bool -> Exp Bool -> Exp Bool
(&&)
.|. :: Exp Bool -> Exp Bool -> Exp Bool
(.|.) = Exp Bool -> Exp Bool -> Exp Bool
(||)
xor :: Exp Bool -> Exp Bool -> Exp Bool
xor = Exp Bool -> Exp Bool -> Exp Bool
forall a. Eq a => Exp a -> Exp a -> Exp Bool
(/=)
complement :: Exp Bool -> Exp Bool
complement = Exp Bool -> Exp Bool
not
shift :: Exp Bool -> Exp Int -> Exp Bool
shift Exp Bool
x Exp Int
i = Exp Bool -> Exp Bool -> Exp Bool -> Exp Bool
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Eq a => Exp a -> Exp a -> Exp Bool
== Exp Int
0) Exp Bool
x (Bool -> Exp Bool
forall e. (HasCallStack, Elt e) => e -> Exp e
constant Bool
False)
testBit :: Exp Bool -> Exp Int -> Exp Bool
testBit Exp Bool
x Exp Int
i = Exp Bool -> Exp Bool -> Exp Bool -> Exp Bool
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Eq a => Exp a -> Exp a -> Exp Bool
== Exp Int
0) Exp Bool
x (Bool -> Exp Bool
forall e. (HasCallStack, Elt e) => e -> Exp e
constant Bool
False)
rotate :: Exp Bool -> Exp Int -> Exp Bool
rotate Exp Bool
x Exp Int
_ = Exp Bool
x
bit :: Exp Int -> Exp Bool
bit Exp Int
i = Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Eq a => Exp a -> Exp a -> Exp Bool
== Exp Int
0
isSigned :: Exp Bool -> Exp Bool
isSigned = Exp Bool -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp Bool -> Exp Int
popCount = Exp Bool -> Exp Int
boolToInt
instance Bits Int where
.&. :: Exp Int -> Exp Int -> Exp Int
(.&.) = Exp Int -> Exp Int -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp Int -> Exp Int -> Exp Int
(.|.) = Exp Int -> Exp Int -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp Int -> Exp Int -> Exp Int
xor = Exp Int -> Exp Int -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp Int -> Exp Int
complement = Exp Int -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp Int
bit = Exp Int -> Exp Int
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault
testBit :: Exp Int -> Exp Int -> Exp Bool
testBit = Exp Int -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault
shift :: Exp Int -> Exp Int -> Exp Int
shift = Exp Int -> Exp Int -> Exp Int
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp Int -> Exp Int -> Exp Int
shiftL = Exp Int -> Exp Int -> Exp Int
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp Int -> Exp Int -> Exp Int
shiftR = Exp Int -> Exp Int -> Exp Int
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp Int -> Exp Int -> Exp Int
unsafeShiftL = Exp Int -> Exp Int -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp Int -> Exp Int -> Exp Int
unsafeShiftR = Exp Int -> Exp Int -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp Int -> Exp Int -> Exp Int
rotate = Exp Int -> Exp Int -> Exp Int
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp Int -> Exp Int -> Exp Int
rotateL = Exp Int -> Exp Int -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp Int -> Exp Int -> Exp Int
rotateR = Exp Int -> Exp Int -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp Int -> Exp Bool
isSigned = Exp Int -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp Int -> Exp Int
popCount = Exp Int -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount
instance Bits Int8 where
.&. :: Exp Int8 -> Exp Int8 -> Exp Int8
(.&.) = Exp Int8 -> Exp Int8 -> Exp Int8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp Int8 -> Exp Int8 -> Exp Int8
(.|.) = Exp Int8 -> Exp Int8 -> Exp Int8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp Int8 -> Exp Int8 -> Exp Int8
xor = Exp Int8 -> Exp Int8 -> Exp Int8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp Int8 -> Exp Int8
complement = Exp Int8 -> Exp Int8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp Int8
bit = Exp Int -> Exp Int8
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault
testBit :: Exp Int8 -> Exp Int -> Exp Bool
testBit = Exp Int8 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault
shift :: Exp Int8 -> Exp Int -> Exp Int8
shift = Exp Int8 -> Exp Int -> Exp Int8
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp Int8 -> Exp Int -> Exp Int8
shiftL = Exp Int8 -> Exp Int -> Exp Int8
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp Int8 -> Exp Int -> Exp Int8
shiftR = Exp Int8 -> Exp Int -> Exp Int8
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp Int8 -> Exp Int -> Exp Int8
unsafeShiftL = Exp Int8 -> Exp Int -> Exp Int8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp Int8 -> Exp Int -> Exp Int8
unsafeShiftR = Exp Int8 -> Exp Int -> Exp Int8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp Int8 -> Exp Int -> Exp Int8
rotate = Exp Int8 -> Exp Int -> Exp Int8
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp Int8 -> Exp Int -> Exp Int8
rotateL = Exp Int8 -> Exp Int -> Exp Int8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp Int8 -> Exp Int -> Exp Int8
rotateR = Exp Int8 -> Exp Int -> Exp Int8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp Int8 -> Exp Bool
isSigned = Exp Int8 -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp Int8 -> Exp Int
popCount = Exp Int8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount
instance Bits Int16 where
.&. :: Exp Int16 -> Exp Int16 -> Exp Int16
(.&.) = Exp Int16 -> Exp Int16 -> Exp Int16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp Int16 -> Exp Int16 -> Exp Int16
(.|.) = Exp Int16 -> Exp Int16 -> Exp Int16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp Int16 -> Exp Int16 -> Exp Int16
xor = Exp Int16 -> Exp Int16 -> Exp Int16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp Int16 -> Exp Int16
complement = Exp Int16 -> Exp Int16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp Int16
bit = Exp Int -> Exp Int16
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault
testBit :: Exp Int16 -> Exp Int -> Exp Bool
testBit = Exp Int16 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault
shift :: Exp Int16 -> Exp Int -> Exp Int16
shift = Exp Int16 -> Exp Int -> Exp Int16
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp Int16 -> Exp Int -> Exp Int16
shiftL = Exp Int16 -> Exp Int -> Exp Int16
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp Int16 -> Exp Int -> Exp Int16
shiftR = Exp Int16 -> Exp Int -> Exp Int16
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp Int16 -> Exp Int -> Exp Int16
unsafeShiftL = Exp Int16 -> Exp Int -> Exp Int16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp Int16 -> Exp Int -> Exp Int16
unsafeShiftR = Exp Int16 -> Exp Int -> Exp Int16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp Int16 -> Exp Int -> Exp Int16
rotate = Exp Int16 -> Exp Int -> Exp Int16
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp Int16 -> Exp Int -> Exp Int16
rotateL = Exp Int16 -> Exp Int -> Exp Int16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp Int16 -> Exp Int -> Exp Int16
rotateR = Exp Int16 -> Exp Int -> Exp Int16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp Int16 -> Exp Bool
isSigned = Exp Int16 -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp Int16 -> Exp Int
popCount = Exp Int16 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount
instance Bits Int32 where
.&. :: Exp Int32 -> Exp Int32 -> Exp Int32
(.&.) = Exp Int32 -> Exp Int32 -> Exp Int32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp Int32 -> Exp Int32 -> Exp Int32
(.|.) = Exp Int32 -> Exp Int32 -> Exp Int32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp Int32 -> Exp Int32 -> Exp Int32
xor = Exp Int32 -> Exp Int32 -> Exp Int32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp Int32 -> Exp Int32
complement = Exp Int32 -> Exp Int32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp Int32
bit = Exp Int -> Exp Int32
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault
testBit :: Exp Int32 -> Exp Int -> Exp Bool
testBit = Exp Int32 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault
shift :: Exp Int32 -> Exp Int -> Exp Int32
shift = Exp Int32 -> Exp Int -> Exp Int32
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp Int32 -> Exp Int -> Exp Int32
shiftL = Exp Int32 -> Exp Int -> Exp Int32
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp Int32 -> Exp Int -> Exp Int32
shiftR = Exp Int32 -> Exp Int -> Exp Int32
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp Int32 -> Exp Int -> Exp Int32
unsafeShiftL = Exp Int32 -> Exp Int -> Exp Int32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp Int32 -> Exp Int -> Exp Int32
unsafeShiftR = Exp Int32 -> Exp Int -> Exp Int32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp Int32 -> Exp Int -> Exp Int32
rotate = Exp Int32 -> Exp Int -> Exp Int32
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp Int32 -> Exp Int -> Exp Int32
rotateL = Exp Int32 -> Exp Int -> Exp Int32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp Int32 -> Exp Int -> Exp Int32
rotateR = Exp Int32 -> Exp Int -> Exp Int32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp Int32 -> Exp Bool
isSigned = Exp Int32 -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp Int32 -> Exp Int
popCount = Exp Int32 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount
instance Bits Int64 where
.&. :: Exp Int64 -> Exp Int64 -> Exp Int64
(.&.) = Exp Int64 -> Exp Int64 -> Exp Int64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp Int64 -> Exp Int64 -> Exp Int64
(.|.) = Exp Int64 -> Exp Int64 -> Exp Int64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp Int64 -> Exp Int64 -> Exp Int64
xor = Exp Int64 -> Exp Int64 -> Exp Int64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp Int64 -> Exp Int64
complement = Exp Int64 -> Exp Int64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp Int64
bit = Exp Int -> Exp Int64
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault
testBit :: Exp Int64 -> Exp Int -> Exp Bool
testBit = Exp Int64 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault
shift :: Exp Int64 -> Exp Int -> Exp Int64
shift = Exp Int64 -> Exp Int -> Exp Int64
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp Int64 -> Exp Int -> Exp Int64
shiftL = Exp Int64 -> Exp Int -> Exp Int64
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp Int64 -> Exp Int -> Exp Int64
shiftR = Exp Int64 -> Exp Int -> Exp Int64
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp Int64 -> Exp Int -> Exp Int64
unsafeShiftL = Exp Int64 -> Exp Int -> Exp Int64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp Int64 -> Exp Int -> Exp Int64
unsafeShiftR = Exp Int64 -> Exp Int -> Exp Int64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp Int64 -> Exp Int -> Exp Int64
rotate = Exp Int64 -> Exp Int -> Exp Int64
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp Int64 -> Exp Int -> Exp Int64
rotateL = Exp Int64 -> Exp Int -> Exp Int64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp Int64 -> Exp Int -> Exp Int64
rotateR = Exp Int64 -> Exp Int -> Exp Int64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp Int64 -> Exp Bool
isSigned = Exp Int64 -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp Int64 -> Exp Int
popCount = Exp Int64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount
instance Bits Word where
.&. :: Exp Word -> Exp Word -> Exp Word
(.&.) = Exp Word -> Exp Word -> Exp Word
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp Word -> Exp Word -> Exp Word
(.|.) = Exp Word -> Exp Word -> Exp Word
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp Word -> Exp Word -> Exp Word
xor = Exp Word -> Exp Word -> Exp Word
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp Word -> Exp Word
complement = Exp Word -> Exp Word
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp Word
bit = Exp Int -> Exp Word
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault
testBit :: Exp Word -> Exp Int -> Exp Bool
testBit = Exp Word -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault
shift :: Exp Word -> Exp Int -> Exp Word
shift = Exp Word -> Exp Int -> Exp Word
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp Word -> Exp Int -> Exp Word
shiftL = Exp Word -> Exp Int -> Exp Word
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp Word -> Exp Int -> Exp Word
shiftR = Exp Word -> Exp Int -> Exp Word
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp Word -> Exp Int -> Exp Word
unsafeShiftL = Exp Word -> Exp Int -> Exp Word
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp Word -> Exp Int -> Exp Word
unsafeShiftR = Exp Word -> Exp Int -> Exp Word
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp Word -> Exp Int -> Exp Word
rotate = Exp Word -> Exp Int -> Exp Word
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp Word -> Exp Int -> Exp Word
rotateL = Exp Word -> Exp Int -> Exp Word
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp Word -> Exp Int -> Exp Word
rotateR = Exp Word -> Exp Int -> Exp Word
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp Word -> Exp Bool
isSigned = Exp Word -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp Word -> Exp Int
popCount = Exp Word -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount
instance Bits Word8 where
.&. :: Exp Word8 -> Exp Word8 -> Exp Word8
(.&.) = Exp Word8 -> Exp Word8 -> Exp Word8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp Word8 -> Exp Word8 -> Exp Word8
(.|.) = Exp Word8 -> Exp Word8 -> Exp Word8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp Word8 -> Exp Word8 -> Exp Word8
xor = Exp Word8 -> Exp Word8 -> Exp Word8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp Word8 -> Exp Word8
complement = Exp Word8 -> Exp Word8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp Word8
bit = Exp Int -> Exp Word8
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault
testBit :: Exp Word8 -> Exp Int -> Exp Bool
testBit = Exp Word8 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault
shift :: Exp Word8 -> Exp Int -> Exp Word8
shift = Exp Word8 -> Exp Int -> Exp Word8
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp Word8 -> Exp Int -> Exp Word8
shiftL = Exp Word8 -> Exp Int -> Exp Word8
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp Word8 -> Exp Int -> Exp Word8
shiftR = Exp Word8 -> Exp Int -> Exp Word8
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp Word8 -> Exp Int -> Exp Word8
unsafeShiftL = Exp Word8 -> Exp Int -> Exp Word8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp Word8 -> Exp Int -> Exp Word8
unsafeShiftR = Exp Word8 -> Exp Int -> Exp Word8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp Word8 -> Exp Int -> Exp Word8
rotate = Exp Word8 -> Exp Int -> Exp Word8
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp Word8 -> Exp Int -> Exp Word8
rotateL = Exp Word8 -> Exp Int -> Exp Word8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp Word8 -> Exp Int -> Exp Word8
rotateR = Exp Word8 -> Exp Int -> Exp Word8
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp Word8 -> Exp Bool
isSigned = Exp Word8 -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp Word8 -> Exp Int
popCount = Exp Word8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount
instance Bits Word16 where
.&. :: Exp Word16 -> Exp Word16 -> Exp Word16
(.&.) = Exp Word16 -> Exp Word16 -> Exp Word16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp Word16 -> Exp Word16 -> Exp Word16
(.|.) = Exp Word16 -> Exp Word16 -> Exp Word16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp Word16 -> Exp Word16 -> Exp Word16
xor = Exp Word16 -> Exp Word16 -> Exp Word16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp Word16 -> Exp Word16
complement = Exp Word16 -> Exp Word16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp Word16
bit = Exp Int -> Exp Word16
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault
testBit :: Exp Word16 -> Exp Int -> Exp Bool
testBit = Exp Word16 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault
shift :: Exp Word16 -> Exp Int -> Exp Word16
shift = Exp Word16 -> Exp Int -> Exp Word16
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp Word16 -> Exp Int -> Exp Word16
shiftL = Exp Word16 -> Exp Int -> Exp Word16
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp Word16 -> Exp Int -> Exp Word16
shiftR = Exp Word16 -> Exp Int -> Exp Word16
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp Word16 -> Exp Int -> Exp Word16
unsafeShiftL = Exp Word16 -> Exp Int -> Exp Word16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp Word16 -> Exp Int -> Exp Word16
unsafeShiftR = Exp Word16 -> Exp Int -> Exp Word16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp Word16 -> Exp Int -> Exp Word16
rotate = Exp Word16 -> Exp Int -> Exp Word16
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp Word16 -> Exp Int -> Exp Word16
rotateL = Exp Word16 -> Exp Int -> Exp Word16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp Word16 -> Exp Int -> Exp Word16
rotateR = Exp Word16 -> Exp Int -> Exp Word16
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp Word16 -> Exp Bool
isSigned = Exp Word16 -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp Word16 -> Exp Int
popCount = Exp Word16 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount
instance Bits Word32 where
.&. :: Exp Word32 -> Exp Word32 -> Exp Word32
(.&.) = Exp Word32 -> Exp Word32 -> Exp Word32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp Word32 -> Exp Word32 -> Exp Word32
(.|.) = Exp Word32 -> Exp Word32 -> Exp Word32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp Word32 -> Exp Word32 -> Exp Word32
xor = Exp Word32 -> Exp Word32 -> Exp Word32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp Word32 -> Exp Word32
complement = Exp Word32 -> Exp Word32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp Word32
bit = Exp Int -> Exp Word32
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault
testBit :: Exp Word32 -> Exp Int -> Exp Bool
testBit = Exp Word32 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault
shift :: Exp Word32 -> Exp Int -> Exp Word32
shift = Exp Word32 -> Exp Int -> Exp Word32
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp Word32 -> Exp Int -> Exp Word32
shiftL = Exp Word32 -> Exp Int -> Exp Word32
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp Word32 -> Exp Int -> Exp Word32
shiftR = Exp Word32 -> Exp Int -> Exp Word32
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp Word32 -> Exp Int -> Exp Word32
unsafeShiftL = Exp Word32 -> Exp Int -> Exp Word32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp Word32 -> Exp Int -> Exp Word32
unsafeShiftR = Exp Word32 -> Exp Int -> Exp Word32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp Word32 -> Exp Int -> Exp Word32
rotate = Exp Word32 -> Exp Int -> Exp Word32
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp Word32 -> Exp Int -> Exp Word32
rotateL = Exp Word32 -> Exp Int -> Exp Word32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp Word32 -> Exp Int -> Exp Word32
rotateR = Exp Word32 -> Exp Int -> Exp Word32
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp Word32 -> Exp Bool
isSigned = Exp Word32 -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp Word32 -> Exp Int
popCount = Exp Word32 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount
instance Bits Word64 where
.&. :: Exp Word64 -> Exp Word64 -> Exp Word64
(.&.) = Exp Word64 -> Exp Word64 -> Exp Word64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp Word64 -> Exp Word64 -> Exp Word64
(.|.) = Exp Word64 -> Exp Word64 -> Exp Word64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp Word64 -> Exp Word64 -> Exp Word64
xor = Exp Word64 -> Exp Word64 -> Exp Word64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp Word64 -> Exp Word64
complement = Exp Word64 -> Exp Word64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp Word64
bit = Exp Int -> Exp Word64
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault
testBit :: Exp Word64 -> Exp Int -> Exp Bool
testBit = Exp Word64 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault
shift :: Exp Word64 -> Exp Int -> Exp Word64
shift = Exp Word64 -> Exp Int -> Exp Word64
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp Word64 -> Exp Int -> Exp Word64
shiftL = Exp Word64 -> Exp Int -> Exp Word64
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp Word64 -> Exp Int -> Exp Word64
shiftR = Exp Word64 -> Exp Int -> Exp Word64
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp Word64 -> Exp Int -> Exp Word64
unsafeShiftL = Exp Word64 -> Exp Int -> Exp Word64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp Word64 -> Exp Int -> Exp Word64
unsafeShiftR = Exp Word64 -> Exp Int -> Exp Word64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp Word64 -> Exp Int -> Exp Word64
rotate = Exp Word64 -> Exp Int -> Exp Word64
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp Word64 -> Exp Int -> Exp Word64
rotateL = Exp Word64 -> Exp Int -> Exp Word64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp Word64 -> Exp Int -> Exp Word64
rotateR = Exp Word64 -> Exp Int -> Exp Word64
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp Word64 -> Exp Bool
isSigned = Exp Word64 -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp Word64 -> Exp Int
popCount = Exp Word64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount
instance Bits CInt where
.&. :: Exp CInt -> Exp CInt -> Exp CInt
(.&.) = Exp CInt -> Exp CInt -> Exp CInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp CInt -> Exp CInt -> Exp CInt
(.|.) = Exp CInt -> Exp CInt -> Exp CInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp CInt -> Exp CInt -> Exp CInt
xor = Exp CInt -> Exp CInt -> Exp CInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp CInt -> Exp CInt
complement = Exp CInt -> Exp CInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp CInt
bit = Exp Int32 -> Exp CInt
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast (Exp Int32 -> Exp CInt)
-> (Exp Int -> Exp Int32) -> Exp Int -> Exp CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IsIntegral (EltR Int32), Bits Int32) => Exp Int -> Exp Int32
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault @Int32
testBit :: Exp CInt -> Exp Int -> Exp Bool
testBit Exp CInt
b = Exp Int32 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault (Exp CInt -> Exp Int32
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int32 Exp CInt
b)
shift :: Exp CInt -> Exp Int -> Exp CInt
shift = Exp CInt -> Exp Int -> Exp CInt
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp CInt -> Exp Int -> Exp CInt
shiftL = Exp CInt -> Exp Int -> Exp CInt
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp CInt -> Exp Int -> Exp CInt
shiftR = Exp CInt -> Exp Int -> Exp CInt
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp CInt -> Exp Int -> Exp CInt
unsafeShiftL = Exp CInt -> Exp Int -> Exp CInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp CInt -> Exp Int -> Exp CInt
unsafeShiftR = Exp CInt -> Exp Int -> Exp CInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp CInt -> Exp Int -> Exp CInt
rotate = Exp CInt -> Exp Int -> Exp CInt
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp CInt -> Exp Int -> Exp CInt
rotateL = Exp CInt -> Exp Int -> Exp CInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp CInt -> Exp Int -> Exp CInt
rotateR = Exp CInt -> Exp Int -> Exp CInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp CInt -> Exp Bool
isSigned = Exp CInt -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp CInt -> Exp Int
popCount = Exp Int32 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount (Exp Int32 -> Exp Int)
-> (Exp CInt -> Exp Int32) -> Exp CInt -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int32, IsScalar (EltR a), IsScalar (EltR Int32),
BitSizeEq (EltR a) (EltR Int32)) =>
Exp a -> Exp Int32
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int32
instance Bits CUInt where
.&. :: Exp CUInt -> Exp CUInt -> Exp CUInt
(.&.) = Exp CUInt -> Exp CUInt -> Exp CUInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp CUInt -> Exp CUInt -> Exp CUInt
(.|.) = Exp CUInt -> Exp CUInt -> Exp CUInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp CUInt -> Exp CUInt -> Exp CUInt
xor = Exp CUInt -> Exp CUInt -> Exp CUInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp CUInt -> Exp CUInt
complement = Exp CUInt -> Exp CUInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp CUInt
bit = Exp Word32 -> Exp CUInt
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast (Exp Word32 -> Exp CUInt)
-> (Exp Int -> Exp Word32) -> Exp Int -> Exp CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IsIntegral (EltR Word32), Bits Word32) => Exp Int -> Exp Word32
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault @Word32
testBit :: Exp CUInt -> Exp Int -> Exp Bool
testBit Exp CUInt
b = Exp Word32 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault (Exp CUInt -> Exp Word32
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word32 Exp CUInt
b)
shift :: Exp CUInt -> Exp Int -> Exp CUInt
shift = Exp CUInt -> Exp Int -> Exp CUInt
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp CUInt -> Exp Int -> Exp CUInt
shiftL = Exp CUInt -> Exp Int -> Exp CUInt
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp CUInt -> Exp Int -> Exp CUInt
shiftR = Exp CUInt -> Exp Int -> Exp CUInt
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp CUInt -> Exp Int -> Exp CUInt
unsafeShiftL = Exp CUInt -> Exp Int -> Exp CUInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp CUInt -> Exp Int -> Exp CUInt
unsafeShiftR = Exp CUInt -> Exp Int -> Exp CUInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp CUInt -> Exp Int -> Exp CUInt
rotate = Exp CUInt -> Exp Int -> Exp CUInt
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp CUInt -> Exp Int -> Exp CUInt
rotateL = Exp CUInt -> Exp Int -> Exp CUInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp CUInt -> Exp Int -> Exp CUInt
rotateR = Exp CUInt -> Exp Int -> Exp CUInt
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp CUInt -> Exp Bool
isSigned = Exp CUInt -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp CUInt -> Exp Int
popCount = Exp Word32 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount (Exp Word32 -> Exp Int)
-> (Exp CUInt -> Exp Word32) -> Exp CUInt -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word32, IsScalar (EltR a), IsScalar (EltR Word32),
BitSizeEq (EltR a) (EltR Word32)) =>
Exp a -> Exp Word32
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word32
instance Bits CLong where
.&. :: Exp CLong -> Exp CLong -> Exp CLong
(.&.) = Exp CLong -> Exp CLong -> Exp CLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp CLong -> Exp CLong -> Exp CLong
(.|.) = Exp CLong -> Exp CLong -> Exp CLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp CLong -> Exp CLong -> Exp CLong
xor = Exp CLong -> Exp CLong -> Exp CLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp CLong -> Exp CLong
complement = Exp CLong -> Exp CLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp CLong
bit = Exp Int64 -> Exp CLong
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast (Exp Int64 -> Exp CLong)
-> (Exp Int -> Exp Int64) -> Exp Int -> Exp CLong
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IsIntegral (EltR Int64), Bits Int64) => Exp Int -> Exp Int64
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault @HTYPE_CLONG
testBit :: Exp CLong -> Exp Int -> Exp Bool
testBit Exp CLong
b = Exp Int64 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault (Exp CLong -> Exp Int64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @HTYPE_CLONG Exp CLong
b)
shift :: Exp CLong -> Exp Int -> Exp CLong
shift = Exp CLong -> Exp Int -> Exp CLong
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp CLong -> Exp Int -> Exp CLong
shiftL = Exp CLong -> Exp Int -> Exp CLong
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp CLong -> Exp Int -> Exp CLong
shiftR = Exp CLong -> Exp Int -> Exp CLong
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp CLong -> Exp Int -> Exp CLong
unsafeShiftL = Exp CLong -> Exp Int -> Exp CLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp CLong -> Exp Int -> Exp CLong
unsafeShiftR = Exp CLong -> Exp Int -> Exp CLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp CLong -> Exp Int -> Exp CLong
rotate = Exp CLong -> Exp Int -> Exp CLong
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp CLong -> Exp Int -> Exp CLong
rotateL = Exp CLong -> Exp Int -> Exp CLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp CLong -> Exp Int -> Exp CLong
rotateR = Exp CLong -> Exp Int -> Exp CLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp CLong -> Exp Bool
isSigned = Exp CLong -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp CLong -> Exp Int
popCount = Exp Int64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount (Exp Int64 -> Exp Int)
-> (Exp CLong -> Exp Int64) -> Exp CLong -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int64, IsScalar (EltR a), IsScalar (EltR Int64),
BitSizeEq (EltR a) (EltR Int64)) =>
Exp a -> Exp Int64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @HTYPE_CLONG
instance Bits CULong where
.&. :: Exp CULong -> Exp CULong -> Exp CULong
(.&.) = Exp CULong -> Exp CULong -> Exp CULong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp CULong -> Exp CULong -> Exp CULong
(.|.) = Exp CULong -> Exp CULong -> Exp CULong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp CULong -> Exp CULong -> Exp CULong
xor = Exp CULong -> Exp CULong -> Exp CULong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp CULong -> Exp CULong
complement = Exp CULong -> Exp CULong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp CULong
bit = Exp Word64 -> Exp CULong
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast (Exp Word64 -> Exp CULong)
-> (Exp Int -> Exp Word64) -> Exp Int -> Exp CULong
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IsIntegral (EltR Word64), Bits Word64) => Exp Int -> Exp Word64
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault @HTYPE_CULONG
testBit :: Exp CULong -> Exp Int -> Exp Bool
testBit Exp CULong
b = Exp Word64 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault (Exp CULong -> Exp Word64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @HTYPE_CULONG Exp CULong
b)
shift :: Exp CULong -> Exp Int -> Exp CULong
shift = Exp CULong -> Exp Int -> Exp CULong
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp CULong -> Exp Int -> Exp CULong
shiftL = Exp CULong -> Exp Int -> Exp CULong
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp CULong -> Exp Int -> Exp CULong
shiftR = Exp CULong -> Exp Int -> Exp CULong
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp CULong -> Exp Int -> Exp CULong
unsafeShiftL = Exp CULong -> Exp Int -> Exp CULong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp CULong -> Exp Int -> Exp CULong
unsafeShiftR = Exp CULong -> Exp Int -> Exp CULong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp CULong -> Exp Int -> Exp CULong
rotate = Exp CULong -> Exp Int -> Exp CULong
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp CULong -> Exp Int -> Exp CULong
rotateL = Exp CULong -> Exp Int -> Exp CULong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp CULong -> Exp Int -> Exp CULong
rotateR = Exp CULong -> Exp Int -> Exp CULong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp CULong -> Exp Bool
isSigned = Exp CULong -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp CULong -> Exp Int
popCount = Exp Word64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount (Exp Word64 -> Exp Int)
-> (Exp CULong -> Exp Word64) -> Exp CULong -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word64, IsScalar (EltR a), IsScalar (EltR Word64),
BitSizeEq (EltR a) (EltR Word64)) =>
Exp a -> Exp Word64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @HTYPE_CULONG
instance Bits CLLong where
.&. :: Exp CLLong -> Exp CLLong -> Exp CLLong
(.&.) = Exp CLLong -> Exp CLLong -> Exp CLLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp CLLong -> Exp CLLong -> Exp CLLong
(.|.) = Exp CLLong -> Exp CLLong -> Exp CLLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp CLLong -> Exp CLLong -> Exp CLLong
xor = Exp CLLong -> Exp CLLong -> Exp CLLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp CLLong -> Exp CLLong
complement = Exp CLLong -> Exp CLLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp CLLong
bit = Exp Int64 -> Exp CLLong
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast (Exp Int64 -> Exp CLLong)
-> (Exp Int -> Exp Int64) -> Exp Int -> Exp CLLong
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IsIntegral (EltR Int64), Bits Int64) => Exp Int -> Exp Int64
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault @Int64
testBit :: Exp CLLong -> Exp Int -> Exp Bool
testBit Exp CLLong
b = Exp Int64 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault (Exp CLLong -> Exp Int64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int64 Exp CLLong
b)
shift :: Exp CLLong -> Exp Int -> Exp CLLong
shift = Exp CLLong -> Exp Int -> Exp CLLong
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp CLLong -> Exp Int -> Exp CLLong
shiftL = Exp CLLong -> Exp Int -> Exp CLLong
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp CLLong -> Exp Int -> Exp CLLong
shiftR = Exp CLLong -> Exp Int -> Exp CLLong
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp CLLong -> Exp Int -> Exp CLLong
unsafeShiftL = Exp CLLong -> Exp Int -> Exp CLLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp CLLong -> Exp Int -> Exp CLLong
unsafeShiftR = Exp CLLong -> Exp Int -> Exp CLLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp CLLong -> Exp Int -> Exp CLLong
rotate = Exp CLLong -> Exp Int -> Exp CLLong
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp CLLong -> Exp Int -> Exp CLLong
rotateL = Exp CLLong -> Exp Int -> Exp CLLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp CLLong -> Exp Int -> Exp CLLong
rotateR = Exp CLLong -> Exp Int -> Exp CLLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp CLLong -> Exp Bool
isSigned = Exp CLLong -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp CLLong -> Exp Int
popCount = Exp Int64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount (Exp Int64 -> Exp Int)
-> (Exp CLLong -> Exp Int64) -> Exp CLLong -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int64, IsScalar (EltR a), IsScalar (EltR Int64),
BitSizeEq (EltR a) (EltR Int64)) =>
Exp a -> Exp Int64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int64
instance Bits CULLong where
.&. :: Exp CULLong -> Exp CULLong -> Exp CULLong
(.&.) = Exp CULLong -> Exp CULLong -> Exp CULLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp CULLong -> Exp CULLong -> Exp CULLong
(.|.) = Exp CULLong -> Exp CULLong -> Exp CULLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp CULLong -> Exp CULLong -> Exp CULLong
xor = Exp CULLong -> Exp CULLong -> Exp CULLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp CULLong -> Exp CULLong
complement = Exp CULLong -> Exp CULLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp CULLong
bit = Exp Word64 -> Exp CULLong
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast (Exp Word64 -> Exp CULLong)
-> (Exp Int -> Exp Word64) -> Exp Int -> Exp CULLong
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IsIntegral (EltR Word64), Bits Word64) => Exp Int -> Exp Word64
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault @Word64
testBit :: Exp CULLong -> Exp Int -> Exp Bool
testBit Exp CULLong
b = Exp Word64 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault (Exp CULLong -> Exp Word64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word64 Exp CULLong
b)
shift :: Exp CULLong -> Exp Int -> Exp CULLong
shift = Exp CULLong -> Exp Int -> Exp CULLong
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp CULLong -> Exp Int -> Exp CULLong
shiftL = Exp CULLong -> Exp Int -> Exp CULLong
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp CULLong -> Exp Int -> Exp CULLong
shiftR = Exp CULLong -> Exp Int -> Exp CULLong
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp CULLong -> Exp Int -> Exp CULLong
unsafeShiftL = Exp CULLong -> Exp Int -> Exp CULLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp CULLong -> Exp Int -> Exp CULLong
unsafeShiftR = Exp CULLong -> Exp Int -> Exp CULLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp CULLong -> Exp Int -> Exp CULLong
rotate = Exp CULLong -> Exp Int -> Exp CULLong
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp CULLong -> Exp Int -> Exp CULLong
rotateL = Exp CULLong -> Exp Int -> Exp CULLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp CULLong -> Exp Int -> Exp CULLong
rotateR = Exp CULLong -> Exp Int -> Exp CULLong
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp CULLong -> Exp Bool
isSigned = Exp CULLong -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp CULLong -> Exp Int
popCount = Exp Word64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount (Exp Word64 -> Exp Int)
-> (Exp CULLong -> Exp Word64) -> Exp CULLong -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word64, IsScalar (EltR a), IsScalar (EltR Word64),
BitSizeEq (EltR a) (EltR Word64)) =>
Exp a -> Exp Word64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word64
instance Bits CShort where
.&. :: Exp CShort -> Exp CShort -> Exp CShort
(.&.) = Exp CShort -> Exp CShort -> Exp CShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp CShort -> Exp CShort -> Exp CShort
(.|.) = Exp CShort -> Exp CShort -> Exp CShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp CShort -> Exp CShort -> Exp CShort
xor = Exp CShort -> Exp CShort -> Exp CShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp CShort -> Exp CShort
complement = Exp CShort -> Exp CShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp CShort
bit = Exp Int16 -> Exp CShort
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast (Exp Int16 -> Exp CShort)
-> (Exp Int -> Exp Int16) -> Exp Int -> Exp CShort
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IsIntegral (EltR Int16), Bits Int16) => Exp Int -> Exp Int16
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault @Int16
testBit :: Exp CShort -> Exp Int -> Exp Bool
testBit Exp CShort
b = Exp Int16 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault (Exp CShort -> Exp Int16
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int16 Exp CShort
b)
shift :: Exp CShort -> Exp Int -> Exp CShort
shift = Exp CShort -> Exp Int -> Exp CShort
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp CShort -> Exp Int -> Exp CShort
shiftL = Exp CShort -> Exp Int -> Exp CShort
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp CShort -> Exp Int -> Exp CShort
shiftR = Exp CShort -> Exp Int -> Exp CShort
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp CShort -> Exp Int -> Exp CShort
unsafeShiftL = Exp CShort -> Exp Int -> Exp CShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp CShort -> Exp Int -> Exp CShort
unsafeShiftR = Exp CShort -> Exp Int -> Exp CShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp CShort -> Exp Int -> Exp CShort
rotate = Exp CShort -> Exp Int -> Exp CShort
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp CShort -> Exp Int -> Exp CShort
rotateL = Exp CShort -> Exp Int -> Exp CShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp CShort -> Exp Int -> Exp CShort
rotateR = Exp CShort -> Exp Int -> Exp CShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp CShort -> Exp Bool
isSigned = Exp CShort -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp CShort -> Exp Int
popCount = Exp Int16 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount (Exp Int16 -> Exp Int)
-> (Exp CShort -> Exp Int16) -> Exp CShort -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int16, IsScalar (EltR a), IsScalar (EltR Int16),
BitSizeEq (EltR a) (EltR Int16)) =>
Exp a -> Exp Int16
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int16
instance Bits CUShort where
.&. :: Exp CUShort -> Exp CUShort -> Exp CUShort
(.&.) = Exp CUShort -> Exp CUShort -> Exp CUShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp CUShort -> Exp CUShort -> Exp CUShort
(.|.) = Exp CUShort -> Exp CUShort -> Exp CUShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp CUShort -> Exp CUShort -> Exp CUShort
xor = Exp CUShort -> Exp CUShort -> Exp CUShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp CUShort -> Exp CUShort
complement = Exp CUShort -> Exp CUShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp CUShort
bit = Exp Word16 -> Exp CUShort
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast (Exp Word16 -> Exp CUShort)
-> (Exp Int -> Exp Word16) -> Exp Int -> Exp CUShort
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IsIntegral (EltR Word16), Bits Word16) => Exp Int -> Exp Word16
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault @Word16
testBit :: Exp CUShort -> Exp Int -> Exp Bool
testBit Exp CUShort
b = Exp Word16 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault (Exp CUShort -> Exp Word16
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word16 Exp CUShort
b)
shift :: Exp CUShort -> Exp Int -> Exp CUShort
shift = Exp CUShort -> Exp Int -> Exp CUShort
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp CUShort -> Exp Int -> Exp CUShort
shiftL = Exp CUShort -> Exp Int -> Exp CUShort
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp CUShort -> Exp Int -> Exp CUShort
shiftR = Exp CUShort -> Exp Int -> Exp CUShort
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp CUShort -> Exp Int -> Exp CUShort
unsafeShiftL = Exp CUShort -> Exp Int -> Exp CUShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp CUShort -> Exp Int -> Exp CUShort
unsafeShiftR = Exp CUShort -> Exp Int -> Exp CUShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp CUShort -> Exp Int -> Exp CUShort
rotate = Exp CUShort -> Exp Int -> Exp CUShort
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp CUShort -> Exp Int -> Exp CUShort
rotateL = Exp CUShort -> Exp Int -> Exp CUShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp CUShort -> Exp Int -> Exp CUShort
rotateR = Exp CUShort -> Exp Int -> Exp CUShort
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp CUShort -> Exp Bool
isSigned = Exp CUShort -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp CUShort -> Exp Int
popCount = Exp Word16 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount (Exp Word16 -> Exp Int)
-> (Exp CUShort -> Exp Word16) -> Exp CUShort -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word16, IsScalar (EltR a), IsScalar (EltR Word16),
BitSizeEq (EltR a) (EltR Word16)) =>
Exp a -> Exp Word16
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word16
instance Bits CChar where
.&. :: Exp CChar -> Exp CChar -> Exp CChar
(.&.) = Exp CChar -> Exp CChar -> Exp CChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp CChar -> Exp CChar -> Exp CChar
(.|.) = Exp CChar -> Exp CChar -> Exp CChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp CChar -> Exp CChar -> Exp CChar
xor = Exp CChar -> Exp CChar -> Exp CChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp CChar -> Exp CChar
complement = Exp CChar -> Exp CChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp CChar
bit = Exp Int8 -> Exp CChar
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast (Exp Int8 -> Exp CChar)
-> (Exp Int -> Exp Int8) -> Exp Int -> Exp CChar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IsIntegral (EltR Int8), Bits Int8) => Exp Int -> Exp Int8
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault @HTYPE_CCHAR
testBit :: Exp CChar -> Exp Int -> Exp Bool
testBit Exp CChar
b = Exp Int8 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault (Exp CChar -> Exp Int8
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @HTYPE_CCHAR Exp CChar
b)
shift :: Exp CChar -> Exp Int -> Exp CChar
shift = Exp CChar -> Exp Int -> Exp CChar
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp CChar -> Exp Int -> Exp CChar
shiftL = Exp CChar -> Exp Int -> Exp CChar
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp CChar -> Exp Int -> Exp CChar
shiftR = Exp CChar -> Exp Int -> Exp CChar
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp CChar -> Exp Int -> Exp CChar
unsafeShiftL = Exp CChar -> Exp Int -> Exp CChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp CChar -> Exp Int -> Exp CChar
unsafeShiftR = Exp CChar -> Exp Int -> Exp CChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp CChar -> Exp Int -> Exp CChar
rotate = Exp CChar -> Exp Int -> Exp CChar
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp CChar -> Exp Int -> Exp CChar
rotateL = Exp CChar -> Exp Int -> Exp CChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp CChar -> Exp Int -> Exp CChar
rotateR = Exp CChar -> Exp Int -> Exp CChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp CChar -> Exp Bool
isSigned = Exp CChar -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp CChar -> Exp Int
popCount = Exp Int8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount (Exp Int8 -> Exp Int)
-> (Exp CChar -> Exp Int8) -> Exp CChar -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int8, IsScalar (EltR a), IsScalar (EltR Int8),
BitSizeEq (EltR a) (EltR Int8)) =>
Exp a -> Exp Int8
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @HTYPE_CCHAR
instance Bits CSChar where
.&. :: Exp CSChar -> Exp CSChar -> Exp CSChar
(.&.) = Exp CSChar -> Exp CSChar -> Exp CSChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp CSChar -> Exp CSChar -> Exp CSChar
(.|.) = Exp CSChar -> Exp CSChar -> Exp CSChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp CSChar -> Exp CSChar -> Exp CSChar
xor = Exp CSChar -> Exp CSChar -> Exp CSChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp CSChar -> Exp CSChar
complement = Exp CSChar -> Exp CSChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp CSChar
bit = Exp Int8 -> Exp CSChar
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast (Exp Int8 -> Exp CSChar)
-> (Exp Int -> Exp Int8) -> Exp Int -> Exp CSChar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IsIntegral (EltR Int8), Bits Int8) => Exp Int -> Exp Int8
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault @Int8
testBit :: Exp CSChar -> Exp Int -> Exp Bool
testBit Exp CSChar
b = Exp Int8 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault (Exp CSChar -> Exp Int8
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int8 Exp CSChar
b)
shift :: Exp CSChar -> Exp Int -> Exp CSChar
shift = Exp CSChar -> Exp Int -> Exp CSChar
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp CSChar -> Exp Int -> Exp CSChar
shiftL = Exp CSChar -> Exp Int -> Exp CSChar
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp CSChar -> Exp Int -> Exp CSChar
shiftR = Exp CSChar -> Exp Int -> Exp CSChar
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp CSChar -> Exp Int -> Exp CSChar
unsafeShiftL = Exp CSChar -> Exp Int -> Exp CSChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp CSChar -> Exp Int -> Exp CSChar
unsafeShiftR = Exp CSChar -> Exp Int -> Exp CSChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp CSChar -> Exp Int -> Exp CSChar
rotate = Exp CSChar -> Exp Int -> Exp CSChar
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp CSChar -> Exp Int -> Exp CSChar
rotateL = Exp CSChar -> Exp Int -> Exp CSChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp CSChar -> Exp Int -> Exp CSChar
rotateR = Exp CSChar -> Exp Int -> Exp CSChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp CSChar -> Exp Bool
isSigned = Exp CSChar -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp CSChar -> Exp Int
popCount = Exp Int8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount (Exp Int8 -> Exp Int)
-> (Exp CSChar -> Exp Int8) -> Exp CSChar -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int8, IsScalar (EltR a), IsScalar (EltR Int8),
BitSizeEq (EltR a) (EltR Int8)) =>
Exp a -> Exp Int8
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int8
instance Bits CUChar where
.&. :: Exp CUChar -> Exp CUChar -> Exp CUChar
(.&.) = Exp CUChar -> Exp CUChar -> Exp CUChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBAnd
.|. :: Exp CUChar -> Exp CUChar -> Exp CUChar
(.|.) = Exp CUChar -> Exp CUChar -> Exp CUChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBOr
xor :: Exp CUChar -> Exp CUChar -> Exp CUChar
xor = Exp CUChar -> Exp CUChar -> Exp CUChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t -> Exp t
mkBXor
complement :: Exp CUChar -> Exp CUChar
complement = Exp CUChar -> Exp CUChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp t
mkBNot
bit :: Exp Int -> Exp CUChar
bit = Exp Word8 -> Exp CUChar
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast (Exp Word8 -> Exp CUChar)
-> (Exp Int -> Exp Word8) -> Exp Int -> Exp CUChar
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IsIntegral (EltR Word8), Bits Word8) => Exp Int -> Exp Word8
forall t. (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault @Word8
testBit :: Exp CUChar -> Exp Int -> Exp Bool
testBit Exp CUChar
b = Exp Word8 -> Exp Int -> Exp Bool
forall t.
(IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp Bool
testBitDefault (Exp CUChar -> Exp Word8
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word8 Exp CUChar
b)
shift :: Exp CUChar -> Exp Int -> Exp CUChar
shift = Exp CUChar -> Exp Int -> Exp CUChar
forall t.
(FiniteBits t, IsIntegral (EltR t), Bits t) =>
Exp t -> Exp Int -> Exp t
shiftDefault
shiftL :: Exp CUChar -> Exp Int -> Exp CUChar
shiftL = Exp CUChar -> Exp Int -> Exp CUChar
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault
shiftR :: Exp CUChar -> Exp Int -> Exp CUChar
shiftR = Exp CUChar -> Exp Int -> Exp CUChar
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault
unsafeShiftL :: Exp CUChar -> Exp Int -> Exp CUChar
unsafeShiftL = Exp CUChar -> Exp Int -> Exp CUChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL
unsafeShiftR :: Exp CUChar -> Exp Int -> Exp CUChar
unsafeShiftR = Exp CUChar -> Exp Int -> Exp CUChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR
rotate :: Exp CUChar -> Exp Int -> Exp CUChar
rotate = Exp CUChar -> Exp Int -> Exp CUChar
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
rotateDefault
rotateL :: Exp CUChar -> Exp Int -> Exp CUChar
rotateL = Exp CUChar -> Exp Int -> Exp CUChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault
rotateR :: Exp CUChar -> Exp Int -> Exp CUChar
rotateR = Exp CUChar -> Exp Int -> Exp CUChar
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault
isSigned :: Exp CUChar -> Exp Bool
isSigned = Exp CUChar -> Exp Bool
forall b. Bits b => Exp b -> Exp Bool
isSignedDefault
popCount :: Exp CUChar -> Exp Int
popCount = Exp Word8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkPopCount (Exp Word8 -> Exp Int)
-> (Exp CUChar -> Exp Word8) -> Exp CUChar -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word8, IsScalar (EltR a), IsScalar (EltR Word8),
BitSizeEq (EltR a) (EltR Word8)) =>
Exp a -> Exp Word8
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word8
instance FiniteBits Bool where
finiteBitSize :: Exp Bool -> Exp Int
finiteBitSize Exp Bool
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt EltR Int
8
countLeadingZeros :: Exp Bool -> Exp Int
countLeadingZeros Exp Bool
x = Exp Bool -> Exp Int -> Exp Int -> Exp Int
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond Exp Bool
x Exp Int
0 Exp Int
1
countTrailingZeros :: Exp Bool -> Exp Int
countTrailingZeros Exp Bool
x = Exp Bool -> Exp Int -> Exp Int -> Exp Int
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond Exp Bool
x Exp Int
0 Exp Int
1
instance FiniteBits Int where
finiteBitSize :: Exp Int -> Exp Int
finiteBitSize Exp Int
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (Int -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (Int
forall a. HasCallStack => a
undefined::Int))
countLeadingZeros :: Exp Int -> Exp Int
countLeadingZeros = Exp Int -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros
countTrailingZeros :: Exp Int -> Exp Int
countTrailingZeros = Exp Int -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros
instance FiniteBits Int8 where
finiteBitSize :: Exp Int8 -> Exp Int
finiteBitSize Exp Int8
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (Int8 -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (Int8
forall a. HasCallStack => a
undefined::Int8))
countLeadingZeros :: Exp Int8 -> Exp Int
countLeadingZeros = Exp Int8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros
countTrailingZeros :: Exp Int8 -> Exp Int
countTrailingZeros = Exp Int8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros
instance FiniteBits Int16 where
finiteBitSize :: Exp Int16 -> Exp Int
finiteBitSize Exp Int16
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (Int16 -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (Int16
forall a. HasCallStack => a
undefined::Int16))
countLeadingZeros :: Exp Int16 -> Exp Int
countLeadingZeros = Exp Int16 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros
countTrailingZeros :: Exp Int16 -> Exp Int
countTrailingZeros = Exp Int16 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros
instance FiniteBits Int32 where
finiteBitSize :: Exp Int32 -> Exp Int
finiteBitSize Exp Int32
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (Int32 -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (Int32
forall a. HasCallStack => a
undefined::Int32))
countLeadingZeros :: Exp Int32 -> Exp Int
countLeadingZeros = Exp Int32 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros
countTrailingZeros :: Exp Int32 -> Exp Int
countTrailingZeros = Exp Int32 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros
instance FiniteBits Int64 where
finiteBitSize :: Exp Int64 -> Exp Int
finiteBitSize Exp Int64
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (Int64 -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (Int64
forall a. HasCallStack => a
undefined::Int64))
countLeadingZeros :: Exp Int64 -> Exp Int
countLeadingZeros = Exp Int64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros
countTrailingZeros :: Exp Int64 -> Exp Int
countTrailingZeros = Exp Int64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros
instance FiniteBits Word where
finiteBitSize :: Exp Word -> Exp Int
finiteBitSize Exp Word
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (Word -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (Word
forall a. HasCallStack => a
undefined::Word))
countLeadingZeros :: Exp Word -> Exp Int
countLeadingZeros = Exp Word -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros
countTrailingZeros :: Exp Word -> Exp Int
countTrailingZeros = Exp Word -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros
instance FiniteBits Word8 where
finiteBitSize :: Exp Word8 -> Exp Int
finiteBitSize Exp Word8
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (Word8 -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (Word8
forall a. HasCallStack => a
undefined::Word8))
countLeadingZeros :: Exp Word8 -> Exp Int
countLeadingZeros = Exp Word8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros
countTrailingZeros :: Exp Word8 -> Exp Int
countTrailingZeros = Exp Word8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros
instance FiniteBits Word16 where
finiteBitSize :: Exp Word16 -> Exp Int
finiteBitSize Exp Word16
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (Word16 -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (Word16
forall a. HasCallStack => a
undefined::Word16))
countLeadingZeros :: Exp Word16 -> Exp Int
countLeadingZeros = Exp Word16 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros
countTrailingZeros :: Exp Word16 -> Exp Int
countTrailingZeros = Exp Word16 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros
instance FiniteBits Word32 where
finiteBitSize :: Exp Word32 -> Exp Int
finiteBitSize Exp Word32
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (Word32 -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (Word32
forall a. HasCallStack => a
undefined::Word32))
countLeadingZeros :: Exp Word32 -> Exp Int
countLeadingZeros = Exp Word32 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros
countTrailingZeros :: Exp Word32 -> Exp Int
countTrailingZeros = Exp Word32 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros
instance FiniteBits Word64 where
finiteBitSize :: Exp Word64 -> Exp Int
finiteBitSize Exp Word64
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (Word64 -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (Word64
forall a. HasCallStack => a
undefined::Word64))
countLeadingZeros :: Exp Word64 -> Exp Int
countLeadingZeros = Exp Word64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros
countTrailingZeros :: Exp Word64 -> Exp Int
countTrailingZeros = Exp Word64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros
instance FiniteBits CInt where
finiteBitSize :: Exp CInt -> Exp Int
finiteBitSize Exp CInt
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (CInt -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (CInt
forall a. HasCallStack => a
undefined::CInt))
countLeadingZeros :: Exp CInt -> Exp Int
countLeadingZeros = Exp Int32 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros (Exp Int32 -> Exp Int)
-> (Exp CInt -> Exp Int32) -> Exp CInt -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int32, IsScalar (EltR a), IsScalar (EltR Int32),
BitSizeEq (EltR a) (EltR Int32)) =>
Exp a -> Exp Int32
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int32
countTrailingZeros :: Exp CInt -> Exp Int
countTrailingZeros = Exp Int32 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros (Exp Int32 -> Exp Int)
-> (Exp CInt -> Exp Int32) -> Exp CInt -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int32, IsScalar (EltR a), IsScalar (EltR Int32),
BitSizeEq (EltR a) (EltR Int32)) =>
Exp a -> Exp Int32
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int32
instance FiniteBits CUInt where
finiteBitSize :: Exp CUInt -> Exp Int
finiteBitSize Exp CUInt
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (CUInt -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (CUInt
forall a. HasCallStack => a
undefined::CUInt))
countLeadingZeros :: Exp CUInt -> Exp Int
countLeadingZeros = Exp Word32 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros (Exp Word32 -> Exp Int)
-> (Exp CUInt -> Exp Word32) -> Exp CUInt -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word32, IsScalar (EltR a), IsScalar (EltR Word32),
BitSizeEq (EltR a) (EltR Word32)) =>
Exp a -> Exp Word32
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word32
countTrailingZeros :: Exp CUInt -> Exp Int
countTrailingZeros = Exp Word32 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros (Exp Word32 -> Exp Int)
-> (Exp CUInt -> Exp Word32) -> Exp CUInt -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word32, IsScalar (EltR a), IsScalar (EltR Word32),
BitSizeEq (EltR a) (EltR Word32)) =>
Exp a -> Exp Word32
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word32
instance FiniteBits CLong where
finiteBitSize :: Exp CLong -> Exp Int
finiteBitSize Exp CLong
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (CLong -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (CLong
forall a. HasCallStack => a
undefined::CLong))
countLeadingZeros :: Exp CLong -> Exp Int
countLeadingZeros = Exp Int64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros (Exp Int64 -> Exp Int)
-> (Exp CLong -> Exp Int64) -> Exp CLong -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int64, IsScalar (EltR a), IsScalar (EltR Int64),
BitSizeEq (EltR a) (EltR Int64)) =>
Exp a -> Exp Int64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @HTYPE_CLONG
countTrailingZeros :: Exp CLong -> Exp Int
countTrailingZeros = Exp Int64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros (Exp Int64 -> Exp Int)
-> (Exp CLong -> Exp Int64) -> Exp CLong -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int64, IsScalar (EltR a), IsScalar (EltR Int64),
BitSizeEq (EltR a) (EltR Int64)) =>
Exp a -> Exp Int64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @HTYPE_CLONG
instance FiniteBits CULong where
finiteBitSize :: Exp CULong -> Exp Int
finiteBitSize Exp CULong
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (CULong -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (CULong
forall a. HasCallStack => a
undefined::CULong))
countLeadingZeros :: Exp CULong -> Exp Int
countLeadingZeros = Exp Word64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros (Exp Word64 -> Exp Int)
-> (Exp CULong -> Exp Word64) -> Exp CULong -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word64, IsScalar (EltR a), IsScalar (EltR Word64),
BitSizeEq (EltR a) (EltR Word64)) =>
Exp a -> Exp Word64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @HTYPE_CULONG
countTrailingZeros :: Exp CULong -> Exp Int
countTrailingZeros = Exp Word64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros (Exp Word64 -> Exp Int)
-> (Exp CULong -> Exp Word64) -> Exp CULong -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word64, IsScalar (EltR a), IsScalar (EltR Word64),
BitSizeEq (EltR a) (EltR Word64)) =>
Exp a -> Exp Word64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @HTYPE_CULONG
instance FiniteBits CLLong where
finiteBitSize :: Exp CLLong -> Exp Int
finiteBitSize Exp CLLong
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (CLLong -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (CLLong
forall a. HasCallStack => a
undefined::CLLong))
countLeadingZeros :: Exp CLLong -> Exp Int
countLeadingZeros = Exp Int64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros (Exp Int64 -> Exp Int)
-> (Exp CLLong -> Exp Int64) -> Exp CLLong -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int64, IsScalar (EltR a), IsScalar (EltR Int64),
BitSizeEq (EltR a) (EltR Int64)) =>
Exp a -> Exp Int64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int64
countTrailingZeros :: Exp CLLong -> Exp Int
countTrailingZeros = Exp Int64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros (Exp Int64 -> Exp Int)
-> (Exp CLLong -> Exp Int64) -> Exp CLLong -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int64, IsScalar (EltR a), IsScalar (EltR Int64),
BitSizeEq (EltR a) (EltR Int64)) =>
Exp a -> Exp Int64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int64
instance FiniteBits CULLong where
finiteBitSize :: Exp CULLong -> Exp Int
finiteBitSize Exp CULLong
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (CULLong -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (CULLong
forall a. HasCallStack => a
undefined::CULLong))
countLeadingZeros :: Exp CULLong -> Exp Int
countLeadingZeros = Exp Word64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros (Exp Word64 -> Exp Int)
-> (Exp CULLong -> Exp Word64) -> Exp CULLong -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word64, IsScalar (EltR a), IsScalar (EltR Word64),
BitSizeEq (EltR a) (EltR Word64)) =>
Exp a -> Exp Word64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word64
countTrailingZeros :: Exp CULLong -> Exp Int
countTrailingZeros = Exp Word64 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros (Exp Word64 -> Exp Int)
-> (Exp CULLong -> Exp Word64) -> Exp CULLong -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word64, IsScalar (EltR a), IsScalar (EltR Word64),
BitSizeEq (EltR a) (EltR Word64)) =>
Exp a -> Exp Word64
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word64
instance FiniteBits CShort where
finiteBitSize :: Exp CShort -> Exp Int
finiteBitSize Exp CShort
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (CShort -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (CShort
forall a. HasCallStack => a
undefined::CShort))
countLeadingZeros :: Exp CShort -> Exp Int
countLeadingZeros = Exp Int16 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros (Exp Int16 -> Exp Int)
-> (Exp CShort -> Exp Int16) -> Exp CShort -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int16, IsScalar (EltR a), IsScalar (EltR Int16),
BitSizeEq (EltR a) (EltR Int16)) =>
Exp a -> Exp Int16
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int16
countTrailingZeros :: Exp CShort -> Exp Int
countTrailingZeros = Exp Int16 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros (Exp Int16 -> Exp Int)
-> (Exp CShort -> Exp Int16) -> Exp CShort -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int16, IsScalar (EltR a), IsScalar (EltR Int16),
BitSizeEq (EltR a) (EltR Int16)) =>
Exp a -> Exp Int16
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int16
instance FiniteBits CUShort where
finiteBitSize :: Exp CUShort -> Exp Int
finiteBitSize Exp CUShort
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (CUShort -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (CUShort
forall a. HasCallStack => a
undefined::CUShort))
countLeadingZeros :: Exp CUShort -> Exp Int
countLeadingZeros = Exp Word16 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros (Exp Word16 -> Exp Int)
-> (Exp CUShort -> Exp Word16) -> Exp CUShort -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word16, IsScalar (EltR a), IsScalar (EltR Word16),
BitSizeEq (EltR a) (EltR Word16)) =>
Exp a -> Exp Word16
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word16
countTrailingZeros :: Exp CUShort -> Exp Int
countTrailingZeros = Exp Word16 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros (Exp Word16 -> Exp Int)
-> (Exp CUShort -> Exp Word16) -> Exp CUShort -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word16, IsScalar (EltR a), IsScalar (EltR Word16),
BitSizeEq (EltR a) (EltR Word16)) =>
Exp a -> Exp Word16
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word16
instance FiniteBits CChar where
finiteBitSize :: Exp CChar -> Exp Int
finiteBitSize Exp CChar
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (CChar -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (CChar
forall a. HasCallStack => a
undefined::CChar))
countLeadingZeros :: Exp CChar -> Exp Int
countLeadingZeros = Exp Int8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros (Exp Int8 -> Exp Int)
-> (Exp CChar -> Exp Int8) -> Exp CChar -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int8, IsScalar (EltR a), IsScalar (EltR Int8),
BitSizeEq (EltR a) (EltR Int8)) =>
Exp a -> Exp Int8
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @HTYPE_CCHAR
countTrailingZeros :: Exp CChar -> Exp Int
countTrailingZeros = Exp Int8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros (Exp Int8 -> Exp Int)
-> (Exp CChar -> Exp Int8) -> Exp CChar -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int8, IsScalar (EltR a), IsScalar (EltR Int8),
BitSizeEq (EltR a) (EltR Int8)) =>
Exp a -> Exp Int8
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @HTYPE_CCHAR
instance FiniteBits CSChar where
finiteBitSize :: Exp CSChar -> Exp Int
finiteBitSize Exp CSChar
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (CSChar -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (CSChar
forall a. HasCallStack => a
undefined::CSChar))
countLeadingZeros :: Exp CSChar -> Exp Int
countLeadingZeros = Exp Int8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros (Exp Int8 -> Exp Int)
-> (Exp CSChar -> Exp Int8) -> Exp CSChar -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int8, IsScalar (EltR a), IsScalar (EltR Int8),
BitSizeEq (EltR a) (EltR Int8)) =>
Exp a -> Exp Int8
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int8
countTrailingZeros :: Exp CSChar -> Exp Int
countTrailingZeros = Exp Int8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros (Exp Int8 -> Exp Int)
-> (Exp CSChar -> Exp Int8) -> Exp CSChar -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Int8, IsScalar (EltR a), IsScalar (EltR Int8),
BitSizeEq (EltR a) (EltR Int8)) =>
Exp a -> Exp Int8
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Int8
instance FiniteBits CUChar where
finiteBitSize :: Exp CUChar -> Exp Int
finiteBitSize Exp CUChar
_ = EltR Int -> Exp Int
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (CUChar -> Int
forall b. FiniteBits b => b -> Int
B.finiteBitSize (CUChar
forall a. HasCallStack => a
undefined::CUChar))
countLeadingZeros :: Exp CUChar -> Exp Int
countLeadingZeros = Exp Word8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountLeadingZeros (Exp Word8 -> Exp Int)
-> (Exp CUChar -> Exp Word8) -> Exp CUChar -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word8, IsScalar (EltR a), IsScalar (EltR Word8),
BitSizeEq (EltR a) (EltR Word8)) =>
Exp a -> Exp Word8
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word8
countTrailingZeros :: Exp CUChar -> Exp Int
countTrailingZeros = Exp Word8 -> Exp Int
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int
mkCountTrailingZeros (Exp Word8 -> Exp Int)
-> (Exp CUChar -> Exp Word8) -> Exp CUChar -> Exp Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Elt a, Elt Word8, IsScalar (EltR a), IsScalar (EltR Word8),
BitSizeEq (EltR a) (EltR Word8)) =>
Exp a -> Exp Word8
forall b a.
(Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b),
BitSizeEq (EltR a) (EltR b)) =>
Exp a -> Exp b
mkBitcast @Word8
bitDefault :: (IsIntegral (EltR t), Bits t) => Exp Int -> Exp t
bitDefault :: Exp Int -> Exp t
bitDefault Exp Int
x = EltR t -> Exp t
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt EltR t
1 Exp t -> Exp Int -> Exp t
forall a. Bits a => Exp a -> Exp Int -> Exp a
`shiftL` Exp Int
x
testBitDefault :: (IsIntegral (EltR t), Bits t) => Exp t -> Exp Int -> Exp Bool
testBitDefault :: Exp t -> Exp Int -> Exp Bool
testBitDefault Exp t
x Exp Int
i = (Exp t
x Exp t -> Exp t -> Exp t
forall a. Bits a => Exp a -> Exp a -> Exp a
.&. Exp Int -> Exp t
forall a. Bits a => Exp Int -> Exp a
bit Exp Int
i) Exp t -> Exp t -> Exp Bool
forall a. Eq a => Exp a -> Exp a -> Exp Bool
/= EltR t -> Exp t
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt EltR t
0
shiftDefault :: (FiniteBits t, IsIntegral (EltR t), B.Bits t) => Exp t -> Exp Int -> Exp t
shiftDefault :: Exp t -> Exp Int -> Exp t
shiftDefault Exp t
x Exp Int
i
= Exp Bool -> Exp t -> Exp t -> Exp t
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Ord a => Exp a -> Exp a -> Exp Bool
>= Exp Int
0) (Exp t -> Exp Int -> Exp t
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftLDefault Exp t
x Exp Int
i)
(Exp t -> Exp Int -> Exp t
forall t.
(Bits t, FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRDefault Exp t
x (-Exp Int
i))
shiftLDefault :: (FiniteBits t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
shiftLDefault :: Exp t -> Exp Int -> Exp t
shiftLDefault Exp t
x Exp Int
i
= Exp Bool -> Exp t -> Exp t -> Exp t
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Ord a => Exp a -> Exp a -> Exp Bool
>= Exp t -> Exp Int
forall b. FiniteBits b => Exp b -> Exp Int
finiteBitSize Exp t
x) (EltR t -> Exp t
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt EltR t
0)
(Exp t -> Exp t) -> Exp t -> Exp t
forall a b. (a -> b) -> a -> b
$ Exp t -> Exp Int -> Exp t
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftL Exp t
x Exp Int
i
shiftRDefault :: forall t. (B.Bits t, FiniteBits t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
shiftRDefault :: Exp t -> Exp Int -> Exp t
shiftRDefault
| t -> Bool
forall a. Bits a => a -> Bool
B.isSigned (t
forall a. HasCallStack => a
undefined::t) = Exp t -> Exp Int -> Exp t
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRADefault
| Bool
otherwise = Exp t -> Exp Int -> Exp t
forall t.
(FiniteBits t, IsIntegral (EltR t)) =>
Exp t -> Exp Int -> Exp t
shiftRLDefault
shiftRADefault :: (FiniteBits t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
shiftRADefault :: Exp t -> Exp Int -> Exp t
shiftRADefault Exp t
x Exp Int
i
= Exp Bool -> Exp t -> Exp t -> Exp t
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Ord a => Exp a -> Exp a -> Exp Bool
>= Exp t -> Exp Int
forall b. FiniteBits b => Exp b -> Exp Int
finiteBitSize Exp t
x) (Exp Bool -> Exp t -> Exp t -> Exp t
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp t -> Exp t -> Exp Bool
forall t. (Elt t, IsSingle (EltR t)) => Exp t -> Exp t -> Exp Bool
mkLt Exp t
x (EltR t -> Exp t
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt EltR t
0)) (EltR t -> Exp t
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt (-EltR t
1)) (EltR t -> Exp t
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt EltR t
0))
(Exp t -> Exp t) -> Exp t -> Exp t
forall a b. (a -> b) -> a -> b
$ Exp t -> Exp Int -> Exp t
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR Exp t
x Exp Int
i
shiftRLDefault :: (FiniteBits t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
shiftRLDefault :: Exp t -> Exp Int -> Exp t
shiftRLDefault Exp t
x Exp Int
i
= Exp Bool -> Exp t -> Exp t -> Exp t
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Ord a => Exp a -> Exp a -> Exp Bool
>= Exp t -> Exp Int
forall b. FiniteBits b => Exp b -> Exp Int
finiteBitSize Exp t
x) (EltR t -> Exp t
forall e. IsIntegral (EltR e) => EltR e -> Exp e
constInt EltR t
0)
(Exp t -> Exp t) -> Exp t -> Exp t
forall a b. (a -> b) -> a -> b
$ Exp t -> Exp Int -> Exp t
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBShiftR Exp t
x Exp Int
i
rotateDefault :: forall t. (FiniteBits t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateDefault :: Exp t -> Exp Int -> Exp t
rotateDefault Exp t
x Exp Int
i
= Exp Bool -> Exp t -> Exp t -> Exp t
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Ord a => Exp a -> Exp a -> Exp Bool
< Exp Int
0) (Exp t -> Exp Int -> Exp t
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBRotateR Exp t
x (-Exp Int
i))
(Exp t -> Exp t) -> Exp t -> Exp t
forall a b. (a -> b) -> a -> b
$ Exp Bool -> Exp t -> Exp t -> Exp t
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Ord a => Exp a -> Exp a -> Exp Bool
> Exp Int
0) (Exp t -> Exp Int -> Exp t
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBRotateL Exp t
x Exp Int
i)
(Exp t -> Exp t) -> Exp t -> Exp t
forall a b. (a -> b) -> a -> b
$ Exp t
x
rotateLDefault :: (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateLDefault :: Exp t -> Exp Int -> Exp t
rotateLDefault Exp t
x Exp Int
i
= Exp Bool -> Exp t -> Exp t -> Exp t
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Eq a => Exp a -> Exp a -> Exp Bool
== Exp Int
0) Exp t
x
(Exp t -> Exp t) -> Exp t -> Exp t
forall a b. (a -> b) -> a -> b
$ Exp t -> Exp Int -> Exp t
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBRotateL Exp t
x Exp Int
i
rotateRDefault :: (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
rotateRDefault :: Exp t -> Exp Int -> Exp t
rotateRDefault Exp t
x Exp Int
i
= Exp Bool -> Exp t -> Exp t -> Exp t
forall t. Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
cond (Exp Int
i Exp Int -> Exp Int -> Exp Bool
forall a. Eq a => Exp a -> Exp a -> Exp Bool
== Exp Int
0) Exp t
x
(Exp t -> Exp t) -> Exp t -> Exp t
forall a b. (a -> b) -> a -> b
$ Exp t -> Exp Int -> Exp t
forall t. (Elt t, IsIntegral (EltR t)) => Exp t -> Exp Int -> Exp t
mkBRotateR Exp t
x Exp Int
i
isSignedDefault :: forall b. B.Bits b => Exp b -> Exp Bool
isSignedDefault :: Exp b -> Exp Bool
isSignedDefault Exp b
_ = Bool -> Exp Bool
forall e. (HasCallStack, Elt e) => e -> Exp e
constant (b -> Bool
forall a. Bits a => a -> Bool
B.isSigned (b
forall a. HasCallStack => a
undefined::b))
constInt :: IsIntegral (EltR e) => EltR e -> Exp e
constInt :: EltR e -> Exp e
constInt = PreSmartExp SmartAcc SmartExp (EltR e) -> Exp e
forall t. PreSmartExp SmartAcc SmartExp (EltR t) -> Exp t
mkExp (PreSmartExp SmartAcc SmartExp (EltR e) -> Exp e)
-> (EltR e -> PreSmartExp SmartAcc SmartExp (EltR e))
-> EltR e
-> Exp e
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScalarType (EltR e)
-> EltR e -> PreSmartExp SmartAcc SmartExp (EltR e)
forall t (acc :: * -> *) (exp :: * -> *).
ScalarType t -> t -> PreSmartExp acc exp t
Const (SingleType (EltR e) -> ScalarType (EltR e)
forall a. SingleType a -> ScalarType a
SingleScalarType (NumType (EltR e) -> SingleType (EltR e)
forall a. NumType a -> SingleType a
NumSingleType (IntegralType (EltR e) -> NumType (EltR e)
forall a. IntegralType a -> NumType a
IntegralNumType IntegralType (EltR e)
forall a. IsIntegral a => IntegralType a
integralType)))