-- |
-- Module      : Basement.Bits
-- License     : BSD-style
-- Maintainer  : Haskell Foundation
-- Stability   : experimental
-- Portability : portable
--

{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NegativeLiterals #-}

#include "MachDeps.h"

module Basement.Bits
    ( BitOps(..)
    , FiniteBitsOps(..)
    , Bits
    , toBits
    , allOne
    ) where

import Basement.Compat.Base
import Basement.Compat.Natural
import Basement.Numerical.Additive
import Basement.Numerical.Subtractive
import Basement.Numerical.Multiplicative
import Basement.Types.OffsetSize
import Basement.Types.Word128 (Word128)
import qualified Basement.Types.Word128 as Word128
import Basement.Types.Word256 (Word256)
import qualified Basement.Types.Word256 as Word256
import Basement.IntegralConv (wordToInt)
import Basement.Nat

import qualified Prelude
import qualified Data.Bits as OldBits
import Data.Maybe (fromMaybe)
import Data.Proxy
import GHC.Base hiding ((.))
import GHC.Prim
import GHC.Types
import GHC.Word
import GHC.Int

#if WORD_SIZE_IN_BITS < 64
import GHC.IntWord64
#endif

-- | operation over finite bits
class FiniteBitsOps bits where
    -- | get the number of bits in the given object
    --
    numberOfBits :: bits -> CountOf Bool

    -- | rotate the given bit set.
    rotateL :: bits -> CountOf Bool -> bits
    -- | rotate the given bit set.
    rotateR :: bits -> CountOf Bool -> bits

    -- | count of number of bit set to 1 in the given bit set.
    popCount :: bits -> CountOf Bool

    -- | reverse all bits in the argument
    bitFlip   :: bits -> bits

    -- | count of the number of leading zeros
    countLeadingZeros :: bits -> CountOf Bool
    default countLeadingZeros :: BitOps bits => bits -> CountOf Bool
    countLeadingZeros n :: bits
n = CountOf Bool -> CountOf Bool -> CountOf Bool
loop CountOf Bool
stop CountOf Bool
forall a. Additive a => a
azero
      where
        stop :: CountOf Bool
stop = bits -> CountOf Bool
forall bits. FiniteBitsOps bits => bits -> CountOf Bool
numberOfBits bits
n
        loop :: CountOf Bool -> CountOf Bool -> CountOf Bool
loop idx :: CountOf Bool
idx count :: CountOf Bool
count
            | CountOf Bool
idx CountOf Bool -> CountOf Bool -> Bool
forall a. Eq a => a -> a -> Bool
== CountOf Bool
forall a. Additive a => a
azero = CountOf Bool
count
            | bits -> Offset Bool -> Bool
forall bits. BitOps bits => bits -> Offset Bool -> Bool
isBitSet bits
n (CountOf Bool -> Offset Bool
forall a. CountOf a -> Offset a
sizeAsOffset CountOf Bool
idx) = CountOf Bool
count
            | Bool
otherwise = CountOf Bool -> CountOf Bool -> CountOf Bool
loop (CountOf Bool -> Maybe (CountOf Bool) -> CountOf Bool
forall a. a -> Maybe a -> a
fromMaybe CountOf Bool
forall a. Additive a => a
azero (CountOf Bool
idx CountOf Bool -> CountOf Bool -> Difference (CountOf Bool)
forall a. Subtractive a => a -> a -> Difference a
- 1)) (CountOf Bool
count CountOf Bool -> CountOf Bool -> CountOf Bool
forall a. Additive a => a -> a -> a
+ 1)

    -- | count of the number of trailing zeros
    countTrailingZeros :: bits -> CountOf Bool
    default countTrailingZeros :: BitOps bits => bits -> CountOf Bool
    countTrailingZeros n :: bits
n = CountOf Bool -> CountOf Bool
loop CountOf Bool
forall a. Additive a => a
azero
      where
        stop :: CountOf Bool
stop = bits -> CountOf Bool
forall bits. FiniteBitsOps bits => bits -> CountOf Bool
numberOfBits bits
n
        loop :: CountOf Bool -> CountOf Bool
loop count :: CountOf Bool
count
            | CountOf Bool
count CountOf Bool -> CountOf Bool -> Bool
forall a. Eq a => a -> a -> Bool
== CountOf Bool
stop = CountOf Bool
count
            | bits -> Offset Bool -> Bool
forall bits. BitOps bits => bits -> Offset Bool -> Bool
isBitSet bits
n (CountOf Bool -> Offset Bool
forall a. CountOf a -> Offset a
sizeAsOffset CountOf Bool
count) = CountOf Bool
count
            | Bool
otherwise = CountOf Bool -> CountOf Bool
loop (CountOf Bool
count CountOf Bool -> CountOf Bool -> CountOf Bool
forall a. Additive a => a -> a -> a
+ 1)

-- | operation over bits
class BitOps bits where
    (.&.)     :: bits -> bits -> bits
    (.|.)     :: bits -> bits -> bits
    (.^.)     :: bits -> bits -> bits
    (.<<.)    :: bits -> CountOf Bool -> bits
    (.>>.)    :: bits -> CountOf Bool -> bits
    -- | construct a bit set with the bit at the given index set.
    bit       :: Offset Bool -> bits
    default bit :: Integral bits => Offset Bool -> bits
    bit n :: Offset Bool
n = 1 bits -> CountOf Bool -> bits
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.<<. (Offset Bool -> CountOf Bool
forall a. Offset a -> CountOf a
offsetAsSize Offset Bool
n)

    -- | test the bit at the given index is set
    isBitSet  :: bits -> Offset Bool -> Bool
    default isBitSet :: (Integral bits, Eq bits) => bits -> Offset Bool -> Bool
    isBitSet x :: bits
x n :: Offset Bool
n = bits
x bits -> bits -> bits
forall bits. BitOps bits => bits -> bits -> bits
.&. (Offset Bool -> bits
forall bits. BitOps bits => Offset Bool -> bits
bit Offset Bool
n) bits -> bits -> Bool
forall a. Eq a => a -> a -> Bool
/= 0

    -- | set the bit at the given index
    setBit    :: bits -> Offset Bool -> bits
    default setBit :: Integral bits => bits -> Offset Bool -> bits
    setBit x :: bits
x n :: Offset Bool
n = bits
x bits -> bits -> bits
forall bits. BitOps bits => bits -> bits -> bits
.|. (Offset Bool -> bits
forall bits. BitOps bits => Offset Bool -> bits
bit Offset Bool
n)

    -- | clear the bit at the given index
    clearBit  :: bits -> Offset Bool -> bits
    default clearBit :: FiniteBitsOps bits => bits -> Offset Bool -> bits
    clearBit x :: bits
x n :: Offset Bool
n = bits
x bits -> bits -> bits
forall bits. BitOps bits => bits -> bits -> bits
.&. (bits -> bits
forall bits. FiniteBitsOps bits => bits -> bits
bitFlip (Offset Bool -> bits
forall bits. BitOps bits => Offset Bool -> bits
bit Offset Bool
n))

infixl 8 .<<., .>>., `rotateL`, `rotateR`
infixl 7 .&.
infixl 6 .^.
infixl 5 .|.

-- | Bool set of 'n' bits.
--
newtype Bits (n :: Nat) = Bits { Bits n -> Natural
bitsToNatural :: Natural }
  deriving (Int -> Bits n -> ShowS
[Bits n] -> ShowS
Bits n -> String
(Int -> Bits n -> ShowS)
-> (Bits n -> String) -> ([Bits n] -> ShowS) -> Show (Bits n)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (n :: Nat). Int -> Bits n -> ShowS
forall (n :: Nat). [Bits n] -> ShowS
forall (n :: Nat). Bits n -> String
showList :: [Bits n] -> ShowS
$cshowList :: forall (n :: Nat). [Bits n] -> ShowS
show :: Bits n -> String
$cshow :: forall (n :: Nat). Bits n -> String
showsPrec :: Int -> Bits n -> ShowS
$cshowsPrec :: forall (n :: Nat). Int -> Bits n -> ShowS
Show, Bits n -> Bits n -> Bool
(Bits n -> Bits n -> Bool)
-> (Bits n -> Bits n -> Bool) -> Eq (Bits n)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (n :: Nat). Bits n -> Bits n -> Bool
/= :: Bits n -> Bits n -> Bool
$c/= :: forall (n :: Nat). Bits n -> Bits n -> Bool
== :: Bits n -> Bits n -> Bool
$c== :: forall (n :: Nat). Bits n -> Bits n -> Bool
Eq, Eq (Bits n)
Eq (Bits n) =>
(Bits n -> Bits n -> Ordering)
-> (Bits n -> Bits n -> Bool)
-> (Bits n -> Bits n -> Bool)
-> (Bits n -> Bits n -> Bool)
-> (Bits n -> Bits n -> Bool)
-> (Bits n -> Bits n -> Bits n)
-> (Bits n -> Bits n -> Bits n)
-> Ord (Bits n)
Bits n -> Bits n -> Bool
Bits n -> Bits n -> Ordering
Bits n -> Bits n -> Bits n
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (n :: Nat). Eq (Bits n)
forall (n :: Nat). Bits n -> Bits n -> Bool
forall (n :: Nat). Bits n -> Bits n -> Ordering
forall (n :: Nat). Bits n -> Bits n -> Bits n
min :: Bits n -> Bits n -> Bits n
$cmin :: forall (n :: Nat). Bits n -> Bits n -> Bits n
max :: Bits n -> Bits n -> Bits n
$cmax :: forall (n :: Nat). Bits n -> Bits n -> Bits n
>= :: Bits n -> Bits n -> Bool
$c>= :: forall (n :: Nat). Bits n -> Bits n -> Bool
> :: Bits n -> Bits n -> Bool
$c> :: forall (n :: Nat). Bits n -> Bits n -> Bool
<= :: Bits n -> Bits n -> Bool
$c<= :: forall (n :: Nat). Bits n -> Bits n -> Bool
< :: Bits n -> Bits n -> Bool
$c< :: forall (n :: Nat). Bits n -> Bits n -> Bool
compare :: Bits n -> Bits n -> Ordering
$ccompare :: forall (n :: Nat). Bits n -> Bits n -> Ordering
$cp1Ord :: forall (n :: Nat). Eq (Bits n)
Ord, Typeable)

-- | convenient Type Constraint Alias fot 'Bits' functions
type SizeValid n = (KnownNat n, 1 <= n)

-- convert an 'Int' into a 'Natural'.
-- This functions is not meant to be exported
lift :: Int -> Natural
lift :: Int -> Natural
lift = Int -> Natural
forall a b. (Integral a, Num b) => a -> b
Prelude.fromIntegral
{-# INLINABLE lift #-}

-- | convert the given 'Natural' into a 'Bits' of size 'n'
--
-- if bits that are not within the boundaries of the 'Bits n' will be truncated.
toBits :: SizeValid n => Natural -> Bits n
toBits :: Natural -> Bits n
toBits nat :: Natural
nat = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits Natural
nat Bits n -> Bits n -> Bits n
forall bits. BitOps bits => bits -> bits -> bits
.&. Bits n
forall (n :: Nat). SizeValid n => Bits n
allOne

-- | construct a 'Bits' with all bits set.
--
-- this function is equivalet to 'maxBound'
allOne :: forall n . SizeValid n => Bits n
allOne :: Bits n
allOne = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits (2 Natural -> Integer -> Natural
forall a b. (Num a, Integral b) => a -> b -> a
Prelude.^ Integer
n Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
Prelude.- Natural
forall a. Multiplicative a => a
midentity)
  where
    n :: Integer
n = Proxy n -> Integer
forall (n :: Nat) (proxy :: Nat -> *).
KnownNat n =>
proxy n -> Integer
natVal (Proxy n
forall k (t :: k). Proxy t
Proxy @n)

instance SizeValid n => Enum (Bits n) where
    toEnum :: Int -> Bits n
toEnum i :: Int
i | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< 0 Bool -> Bool -> Bool
&& Int -> Natural
lift Int
i Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
> Bits n -> Natural
forall (n :: Nat). Bits n -> Natural
bitsToNatural Bits n
maxi = String -> Bits n
forall a. HasCallStack => String -> a
error "Bits n not within bound"
             | Bool
otherwise                            = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits (Int -> Natural
lift Int
i)
      where maxi :: Bits n
maxi = Bits n
forall (n :: Nat). SizeValid n => Bits n
allOne :: Bits n
    fromEnum :: Bits n -> Int
fromEnum (Bits n :: Natural
n) = Natural -> Int
forall a. Enum a => a -> Int
fromEnum Natural
n
instance SizeValid n => Bounded (Bits n) where
    minBound :: Bits n
minBound = Bits n
forall a. Additive a => a
azero
    maxBound :: Bits n
maxBound = Bits n
forall (n :: Nat). SizeValid n => Bits n
allOne
instance SizeValid n => Additive (Bits n) where
    azero :: Bits n
azero = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits 0
    + :: Bits n -> Bits n -> Bits n
(+) (Bits a :: Natural
a) (Bits b :: Natural
b) = Natural -> Bits n
forall (n :: Nat). SizeValid n => Natural -> Bits n
toBits (Natural
a Natural -> Natural -> Natural
forall a. Additive a => a -> a -> a
+ Natural
b)
    scale :: n -> Bits n -> Bits n
scale n :: n
n (Bits a :: Natural
a) = Natural -> Bits n
forall (n :: Nat). SizeValid n => Natural -> Bits n
toBits (n -> Natural -> Natural
forall a n. (Additive a, IsNatural n) => n -> a -> a
scale n
n Natural
a)
instance SizeValid n => Subtractive (Bits n) where
    type Difference (Bits n) = Bits n
    (-) (Bits a :: Natural
a) (Bits b :: Natural
b) = Bits n -> (Natural -> Bits n) -> Maybe Natural -> Bits n
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bits n
forall a. Additive a => a
azero Natural -> Bits n
forall (n :: Nat). SizeValid n => Natural -> Bits n
toBits (Natural
a Natural -> Natural -> Difference Natural
forall a. Subtractive a => a -> a -> Difference a
- Natural
b)
instance SizeValid n => Multiplicative (Bits n) where
    midentity :: Bits n
midentity = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits 1
    * :: Bits n -> Bits n -> Bits n
(*) (Bits a :: Natural
a) (Bits b :: Natural
b) = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits (Natural
a Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
Prelude.* Natural
b)
instance SizeValid n => IDivisible (Bits n) where
    div :: Bits n -> Bits n -> Bits n
div (Bits a :: Natural
a) (Bits b :: Natural
b) = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits (Natural
a Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
`Prelude.div` Natural
b)
    mod :: Bits n -> Bits n -> Bits n
mod (Bits a :: Natural
a) (Bits b :: Natural
b) = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits (Natural
a Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
`Prelude.mod` Natural
b)
    divMod :: Bits n -> Bits n -> (Bits n, Bits n)
divMod (Bits a :: Natural
a) (Bits b :: Natural
b) = let (q :: Natural
q, r :: Natural
r) = Natural -> Natural -> (Natural, Natural)
forall a. Integral a => a -> a -> (a, a)
Prelude.divMod Natural
a Natural
b in (Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits Natural
q, Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits Natural
r)

instance SizeValid n => BitOps (Bits n) where
    .&. :: Bits n -> Bits n -> Bits n
(.&.)    (Bits a :: Natural
a) (Bits b :: Natural
b)    = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits (Natural
a Natural -> Natural -> Natural
forall a. Bits a => a -> a -> a
OldBits..&. Natural
b)
    .|. :: Bits n -> Bits n -> Bits n
(.|.)    (Bits a :: Natural
a) (Bits b :: Natural
b)    = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits (Natural
a Natural -> Natural -> Natural
forall a. Bits a => a -> a -> a
OldBits..|. Natural
b)
    .^. :: Bits n -> Bits n -> Bits n
(.^.)    (Bits a :: Natural
a) (Bits b :: Natural
b)    = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits (Natural
a Natural -> Natural -> Natural
forall a. Bits a => a -> a -> a
`OldBits.xor` Natural
b)
    .<<. :: Bits n -> CountOf Bool -> Bits n
(.<<.)   (Bits a :: Natural
a) (CountOf w :: Int
w) = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits (Natural
a Natural -> Int -> Natural
forall a. Bits a => a -> Int -> a
`OldBits.shiftL` Int
w)
    .>>. :: Bits n -> CountOf Bool -> Bits n
(.>>.)   (Bits a :: Natural
a) (CountOf w :: Int
w) = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits (Natural
a Natural -> Int -> Natural
forall a. Bits a => a -> Int -> a
`OldBits.shiftR` Int
w)
    bit :: Offset Bool -> Bits n
bit               (Offset w :: Int
w)  = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits (Int -> Natural
forall a. Bits a => Int -> a
OldBits.bit Int
w)
    isBitSet :: Bits n -> Offset Bool -> Bool
isBitSet (Bits a :: Natural
a) (Offset w :: Int
w)  = Natural -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
OldBits.testBit Natural
a Int
w
    setBit :: Bits n -> Offset Bool -> Bits n
setBit   (Bits a :: Natural
a) (Offset w :: Int
w)  = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits (Natural -> Int -> Natural
forall a. Bits a => a -> Int -> a
OldBits.setBit Natural
a Int
w)
    clearBit :: Bits n -> Offset Bool -> Bits n
clearBit (Bits a :: Natural
a) (Offset w :: Int
w)  = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits (Natural -> Int -> Natural
forall a. Bits a => a -> Int -> a
OldBits.clearBit Natural
a Int
w)
instance (SizeValid n, NatWithinBound (CountOf Bool) n) => FiniteBitsOps (Bits n) where
    bitFlip :: Bits n -> Bits n
bitFlip (Bits a :: Natural
a) = Natural -> Bits n
forall (n :: Nat). Natural -> Bits n
Bits (Natural -> Natural
forall a. Bits a => a -> a
OldBits.complement Natural
a)
    numberOfBits :: Bits n -> CountOf Bool
numberOfBits _ = Proxy n -> CountOf Bool
forall (n :: Nat) ty (proxy :: Nat -> *).
(KnownNat n, NatWithinBound (CountOf ty) n) =>
proxy n -> CountOf ty
natValCountOf (Proxy n
forall k (t :: k). Proxy t
Proxy @n)
    rotateL :: Bits n -> CountOf Bool -> Bits n
rotateL a :: Bits n
a i :: CountOf Bool
i = (Bits n
a Bits n -> CountOf Bool -> Bits n
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.<<. CountOf Bool
i) Bits n -> Bits n -> Bits n
forall bits. BitOps bits => bits -> bits -> bits
.|. (Bits n
a Bits n -> CountOf Bool -> Bits n
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.>>. CountOf Bool
d)
      where
        n :: CountOf Bool
n = Proxy n -> CountOf Bool
forall (n :: Nat) ty (proxy :: Nat -> *).
(KnownNat n, NatWithinBound (CountOf ty) n) =>
proxy n -> CountOf ty
natValCountOf (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)
        d :: CountOf Bool
d = CountOf Bool -> Maybe (CountOf Bool) -> CountOf Bool
forall a. a -> Maybe a -> a
fromMaybe (CountOf Bool -> Maybe (CountOf Bool) -> CountOf Bool
forall a. a -> Maybe a -> a
fromMaybe (String -> CountOf Bool
forall a. HasCallStack => String -> a
error "impossible") (CountOf Bool
i CountOf Bool -> CountOf Bool -> Difference (CountOf Bool)
forall a. Subtractive a => a -> a -> Difference a
- CountOf Bool
n)) (CountOf Bool
n CountOf Bool -> CountOf Bool -> Difference (CountOf Bool)
forall a. Subtractive a => a -> a -> Difference a
- CountOf Bool
i)
    rotateR :: Bits n -> CountOf Bool -> Bits n
rotateR a :: Bits n
a i :: CountOf Bool
i = (Bits n
a Bits n -> CountOf Bool -> Bits n
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.>>. CountOf Bool
i) Bits n -> Bits n -> Bits n
forall bits. BitOps bits => bits -> bits -> bits
.|. (Bits n
a Bits n -> CountOf Bool -> Bits n
forall bits. BitOps bits => bits -> CountOf Bool -> bits
.<<. CountOf Bool
d)
      where
        n :: CountOf Bool
n = Proxy n -> CountOf Bool
forall (n :: Nat) ty (proxy :: Nat -> *).
(KnownNat n, NatWithinBound (CountOf ty) n) =>
proxy n -> CountOf ty
natValCountOf (Proxy n
forall k (t :: k). Proxy t
Proxy :: Proxy n)
        d :: CountOf Bool
d = CountOf Bool -> Maybe (CountOf Bool) -> CountOf Bool
forall a. a -> Maybe a -> a
fromMaybe (CountOf Bool -> Maybe (CountOf Bool) -> CountOf Bool
forall a. a -> Maybe a -> a
fromMaybe (String -> CountOf Bool
forall a. HasCallStack => String -> a
error "impossible") (CountOf Bool
i CountOf Bool -> CountOf Bool -> Difference (CountOf Bool)
forall a. Subtractive a => a -> a -> Difference a
- CountOf Bool
n)) (CountOf Bool
n CountOf Bool -> CountOf Bool -> Difference (CountOf Bool)
forall a. Subtractive a => a -> a -> Difference a
- CountOf Bool
i)
    popCount :: Bits n -> CountOf Bool
popCount (Bits n :: Natural
n) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Natural -> Int
forall a. Bits a => a -> Int
OldBits.popCount Natural
n)

-- Bool ------------------------------------------------------------------------

instance FiniteBitsOps Bool where
    numberOfBits :: Bool -> CountOf Bool
numberOfBits _ = 1
    rotateL :: Bool -> CountOf Bool -> Bool
rotateL x :: Bool
x _ = Bool
x
    rotateR :: Bool -> CountOf Bool -> Bool
rotateR x :: Bool
x _ = Bool
x
    popCount :: Bool -> CountOf Bool
popCount True = 1
    popCount False = 0
    bitFlip :: Bool -> Bool
bitFlip  = Bool -> Bool
not
    countLeadingZeros :: Bool -> CountOf Bool
countLeadingZeros True  = 0
    countLeadingZeros False = 1
    countTrailingZeros :: Bool -> CountOf Bool
countTrailingZeros True  = 0
    countTrailingZeros False = 1
instance BitOps Bool where
    .&. :: Bool -> Bool -> Bool
(.&.) = Bool -> Bool -> Bool
(&&)
    .|. :: Bool -> Bool -> Bool
(.|.) = Bool -> Bool -> Bool
(||)
    .^. :: Bool -> Bool -> Bool
(.^.) = Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
(/=)
    x :: Bool
x .<<. :: Bool -> CountOf Bool -> Bool
.<<. 0 = Bool
x
    _ .<<. _ = Bool
False
    x :: Bool
x .>>. :: Bool -> CountOf Bool -> Bool
.>>. 0 = Bool
x
    _ .>>. _ = Bool
False
    bit :: Offset Bool -> Bool
bit 0 = Bool
True
    bit _ = Bool
False
    isBitSet :: Bool -> Offset Bool -> Bool
isBitSet x :: Bool
x 0 = Bool
x
    isBitSet _ _ = Bool
False
    setBit :: Bool -> Offset Bool -> Bool
setBit _ 0 = Bool
True
    setBit _ _ = Bool
False
    clearBit :: Bool -> Offset Bool -> Bool
clearBit _ 0 = Bool
False
    clearBit x :: Bool
x _ = Bool
x

-- Word8 ----------------------------------------------------------------------

instance FiniteBitsOps Word8 where
    numberOfBits :: Word8 -> CountOf Bool
numberOfBits _ = 8
    rotateL :: Word8 -> CountOf Bool -> Word8
rotateL (W8# x# :: Word#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Word# -> Word8
W8# Word#
x#
        | Bool
otherwise  = Word# -> Word8
W8# (Word# -> Word#
narrow8Word# ((Word#
x# Word# -> Int# -> Word#
`uncheckedShiftL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
                                          (Word#
x# Word# -> Int# -> Word#
`uncheckedShiftRL#` (8# Int# -> Int# -> Int#
-# Int#
i'#))))
      where
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 7##)
    rotateR :: Word8 -> CountOf Bool -> Word8
rotateR (W8# x# :: Word#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Word# -> Word8
W8# Word#
x#
        | Bool
otherwise  = Word# -> Word8
W8# (Word# -> Word#
narrow8Word# ((Word#
x# Word# -> Int# -> Word#
`uncheckedShiftRL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
                                          (Word#
x# Word# -> Int# -> Word#
`uncheckedShiftL#` (8# Int# -> Int# -> Int#
-# Int#
i'#))))
      where
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 7##)
    bitFlip :: Word8 -> Word8
bitFlip (W8# x# :: Word#
x#) = Word# -> Word8
W8# (Word#
x# Word# -> Word# -> Word#
`xor#` Word#
mb#)
        where !(W8# mb# :: Word#
mb#) = Word8
forall a. Bounded a => a
maxBound
    popCount :: Word8 -> CountOf Bool
popCount (W8# x# :: Word#
x#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
popCnt8# Word#
x#))
    countLeadingZeros :: Word8 -> CountOf Bool
countLeadingZeros (W8# w# :: Word#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
clz8# Word#
w#))
    countTrailingZeros :: Word8 -> CountOf Bool
countTrailingZeros (W8# w# :: Word#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
ctz8# Word#
w#))
instance BitOps Word8 where
    (W8# x# :: Word#
x#) .&. :: Word8 -> Word8 -> Word8
.&. (W8# y# :: Word#
y#)   = Word# -> Word8
W8# (Word#
x# Word# -> Word# -> Word#
`and#` Word#
y#)
    (W8# x# :: Word#
x#) .|. :: Word8 -> Word8 -> Word8
.|. (W8# y# :: Word#
y#)   = Word# -> Word8
W8# (Word#
x# Word# -> Word# -> Word#
`or#`  Word#
y#)
    (W8# x# :: Word#
x#) .^. :: Word8 -> Word8 -> Word8
.^. (W8# y# :: Word#
y#)   = Word# -> Word8
W8# (Word#
x# Word# -> Word# -> Word#
`xor#` Word#
y#)
    (W8# x# :: Word#
x#) .<<. :: Word8 -> CountOf Bool -> Word8
.<<. (CountOf (I# i# :: Int#
i#)) = Word# -> Word8
W8# (Word# -> Word#
narrow8Word# (Word#
x# Word# -> Int# -> Word#
`shiftL#` Int#
i#))
    (W8# x# :: Word#
x#) .>>. :: Word8 -> CountOf Bool -> Word8
.>>. (CountOf (I# i# :: Int#
i#)) = Word# -> Word8
W8# (Word# -> Word#
narrow8Word# (Word#
x# Word# -> Int# -> Word#
`shiftRL#` Int#
i#))

-- Word16 ---------------------------------------------------------------------

instance FiniteBitsOps Word16 where
    numberOfBits :: Word16 -> CountOf Bool
numberOfBits _ = 16
    rotateL :: Word16 -> CountOf Bool -> Word16
rotateL (W16# x# :: Word#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Word# -> Word16
W16# Word#
x#
        | Bool
otherwise  = Word# -> Word16
W16# (Word# -> Word#
narrow16Word# ((Word#
x# Word# -> Int# -> Word#
`uncheckedShiftL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
                                            (Word#
x# Word# -> Int# -> Word#
`uncheckedShiftRL#` (16# Int# -> Int# -> Int#
-# Int#
i'#))))
      where
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 15##)
    rotateR :: Word16 -> CountOf Bool -> Word16
rotateR (W16# x# :: Word#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Word# -> Word16
W16# Word#
x#
        | Bool
otherwise  = Word# -> Word16
W16# (Word# -> Word#
narrow16Word# ((Word#
x# Word# -> Int# -> Word#
`uncheckedShiftRL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
                                            (Word#
x# Word# -> Int# -> Word#
`uncheckedShiftL#` (16# Int# -> Int# -> Int#
-# Int#
i'#))))
      where
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 15##)
    bitFlip :: Word16 -> Word16
bitFlip (W16# x# :: Word#
x#) = Word# -> Word16
W16# (Word#
x# Word# -> Word# -> Word#
`xor#` Word#
mb#)
        where !(W16# mb# :: Word#
mb#) = Word16
forall a. Bounded a => a
maxBound
    popCount :: Word16 -> CountOf Bool
popCount (W16# x# :: Word#
x#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
popCnt16# Word#
x#))
    countLeadingZeros :: Word16 -> CountOf Bool
countLeadingZeros (W16# w# :: Word#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
clz16# Word#
w#))
    countTrailingZeros :: Word16 -> CountOf Bool
countTrailingZeros (W16# w# :: Word#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
ctz16# Word#
w#))
instance BitOps Word16 where
    (W16# x# :: Word#
x#) .&. :: Word16 -> Word16 -> Word16
.&. (W16# y# :: Word#
y#)   = Word# -> Word16
W16# (Word#
x# Word# -> Word# -> Word#
`and#` Word#
y#)
    (W16# x# :: Word#
x#) .|. :: Word16 -> Word16 -> Word16
.|. (W16# y# :: Word#
y#)   = Word# -> Word16
W16# (Word#
x# Word# -> Word# -> Word#
`or#`  Word#
y#)
    (W16# x# :: Word#
x#) .^. :: Word16 -> Word16 -> Word16
.^. (W16# y# :: Word#
y#)   = Word# -> Word16
W16# (Word#
x# Word# -> Word# -> Word#
`xor#` Word#
y#)
    (W16# x# :: Word#
x#) .<<. :: Word16 -> CountOf Bool -> Word16
.<<. (CountOf (I# i# :: Int#
i#)) = Word# -> Word16
W16# (Word# -> Word#
narrow16Word# (Word#
x# Word# -> Int# -> Word#
`shiftL#` Int#
i#))
    (W16# x# :: Word#
x#) .>>. :: Word16 -> CountOf Bool -> Word16
.>>. (CountOf (I# i# :: Int#
i#)) = Word# -> Word16
W16# (Word# -> Word#
narrow16Word# (Word#
x# Word# -> Int# -> Word#
`shiftRL#` Int#
i#))

-- Word32 ---------------------------------------------------------------------

instance FiniteBitsOps Word32 where
    numberOfBits :: Word32 -> CountOf Bool
numberOfBits _ = 32
    rotateL :: Word32 -> CountOf Bool -> Word32
rotateL (W32# x# :: Word#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Word# -> Word32
W32# Word#
x#
        | Bool
otherwise  = Word# -> Word32
W32# (Word# -> Word#
narrow32Word# ((Word#
x# Word# -> Int# -> Word#
`uncheckedShiftL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
                                            (Word#
x# Word# -> Int# -> Word#
`uncheckedShiftRL#` (32# Int# -> Int# -> Int#
-# Int#
i'#))))
      where
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 31##)
    rotateR :: Word32 -> CountOf Bool -> Word32
rotateR (W32# x# :: Word#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Word# -> Word32
W32# Word#
x#
        | Bool
otherwise  = Word# -> Word32
W32# (Word# -> Word#
narrow32Word# ((Word#
x# Word# -> Int# -> Word#
`uncheckedShiftRL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
                                            (Word#
x# Word# -> Int# -> Word#
`uncheckedShiftL#` (32# Int# -> Int# -> Int#
-# Int#
i'#))))
      where
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 31##)
    bitFlip :: Word32 -> Word32
bitFlip (W32# x# :: Word#
x#) = Word# -> Word32
W32# (Word#
x# Word# -> Word# -> Word#
`xor#` Word#
mb#)
        where !(W32# mb# :: Word#
mb#) = Word32
forall a. Bounded a => a
maxBound
    popCount :: Word32 -> CountOf Bool
popCount (W32# x# :: Word#
x#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
popCnt32# Word#
x#))
    countLeadingZeros :: Word32 -> CountOf Bool
countLeadingZeros (W32# w# :: Word#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
clz32# Word#
w#))
    countTrailingZeros :: Word32 -> CountOf Bool
countTrailingZeros (W32# w# :: Word#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
ctz32# Word#
w#))
instance BitOps Word32 where
    (W32# x# :: Word#
x#) .&. :: Word32 -> Word32 -> Word32
.&. (W32# y# :: Word#
y#)   = Word# -> Word32
W32# (Word#
x# Word# -> Word# -> Word#
`and#` Word#
y#)
    (W32# x# :: Word#
x#) .|. :: Word32 -> Word32 -> Word32
.|. (W32# y# :: Word#
y#)   = Word# -> Word32
W32# (Word#
x# Word# -> Word# -> Word#
`or#`  Word#
y#)
    (W32# x# :: Word#
x#) .^. :: Word32 -> Word32 -> Word32
.^. (W32# y# :: Word#
y#)   = Word# -> Word32
W32# (Word#
x# Word# -> Word# -> Word#
`xor#` Word#
y#)
    (W32# x# :: Word#
x#) .<<. :: Word32 -> CountOf Bool -> Word32
.<<. (CountOf (I# i# :: Int#
i#)) = Word# -> Word32
W32# (Word# -> Word#
narrow32Word# (Word#
x# Word# -> Int# -> Word#
`shiftL#` Int#
i#))
    (W32# x# :: Word#
x#) .>>. :: Word32 -> CountOf Bool -> Word32
.>>. (CountOf (I# i# :: Int#
i#)) = Word# -> Word32
W32# (Word# -> Word#
narrow32Word# (Word#
x# Word# -> Int# -> Word#
`shiftRL#` Int#
i#))

-- Word ---------------------------------------------------------------------

#if WORD_SIZE_IN_BITS == 64
instance FiniteBitsOps Word where
    numberOfBits _ = 64
    rotateL (W# x#) (CountOf (I# i#))
        | isTrue# (i'# ==# 0#) = W# x#
        | otherwise  = W# ((x# `uncheckedShiftL#` i'#) `or#`
                           (x# `uncheckedShiftRL#` (64# -# i'#)))
      where
        !i'# = word2Int# (int2Word# i# `and#` 63##)
    rotateR (W# x#) (CountOf (I# i#))
        | isTrue# (i'# ==# 0#) = W# x#
        | otherwise  = W# ((x# `uncheckedShiftRL#` i'#) `or#`
                           (x# `uncheckedShiftL#` (64# -# i'#)))
      where
        !i'# = word2Int# (int2Word# i# `and#` 63##)
    bitFlip (W# x#) = W# (x# `xor#` mb#)
        where !(W# mb#) = maxBound
    popCount (W# x#) = CountOf $ wordToInt (W# (popCnt64# x#))
    countLeadingZeros (W# w#) = CountOf $ wordToInt (W# (clz64# w#))
    countTrailingZeros (W# w#) = CountOf $ wordToInt (W# (ctz64# w#))
#else
instance FiniteBitsOps Word where
    numberOfBits :: Word -> CountOf Bool
numberOfBits _ = 32
    rotateL :: Word -> CountOf Bool -> Word
rotateL (W# x# :: Word#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Word# -> Word
W# Word#
x#
        | Bool
otherwise  = Word# -> Word
W# ((Word#
x# Word# -> Int# -> Word#
`uncheckedShiftL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
                           (Word#
x# Word# -> Int# -> Word#
`uncheckedShiftRL#` (32# Int# -> Int# -> Int#
-# Int#
i'#)))
      where
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 31##)
    rotateR :: Word -> CountOf Bool -> Word
rotateR (W# x# :: Word#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Word# -> Word
W# Word#
x#
        | Bool
otherwise  = Word# -> Word
W# ((Word#
x# Word# -> Int# -> Word#
`uncheckedShiftRL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
                           (Word#
x# Word# -> Int# -> Word#
`uncheckedShiftL#` (32# Int# -> Int# -> Int#
-# Int#
i'#)))
      where
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 31##)
    bitFlip :: Word -> Word
bitFlip (W# x# :: Word#
x#) = Word# -> Word
W# (Word#
x# Word# -> Word# -> Word#
`xor#` Word#
mb#)
        where !(W# mb# :: Word#
mb#) = Word
forall a. Bounded a => a
maxBound
    popCount :: Word -> CountOf Bool
popCount (W# x# :: Word#
x#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
popCnt32# Word#
x#))
    countLeadingZeros :: Word -> CountOf Bool
countLeadingZeros (W# w# :: Word#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
clz32# Word#
w#))
    countTrailingZeros :: Word -> CountOf Bool
countTrailingZeros (W# w# :: Word#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
ctz32# Word#
w#))
#endif

instance BitOps Word where
    (W# x# :: Word#
x#) .&. :: Word -> Word -> Word
.&. (W# y# :: Word#
y#)   = Word# -> Word
W# (Word#
x# Word# -> Word# -> Word#
`and#` Word#
y#)
    (W# x# :: Word#
x#) .|. :: Word -> Word -> Word
.|. (W# y# :: Word#
y#)   = Word# -> Word
W# (Word#
x# Word# -> Word# -> Word#
`or#`  Word#
y#)
    (W# x# :: Word#
x#) .^. :: Word -> Word -> Word
.^. (W# y# :: Word#
y#)   = Word# -> Word
W# (Word#
x# Word# -> Word# -> Word#
`xor#` Word#
y#)
    (W# x# :: Word#
x#) .<<. :: Word -> CountOf Bool -> Word
.<<. (CountOf (I# i# :: Int#
i#)) = Word# -> Word
W# ((Word#
x# Word# -> Int# -> Word#
`shiftL#` Int#
i#))
    (W# x# :: Word#
x#) .>>. :: Word -> CountOf Bool -> Word
.>>. (CountOf (I# i# :: Int#
i#)) = Word# -> Word
W# ((Word#
x# Word# -> Int# -> Word#
`shiftRL#` Int#
i#))

-- Word64 ---------------------------------------------------------------------

#if WORD_SIZE_IN_BITS == 64
instance FiniteBitsOps Word64 where
    numberOfBits _ = 64
    rotateL (W64# x#) (CountOf (I# i#))
        | isTrue# (i'# ==# 0#) = W64# x#
        | otherwise  = W64# ((x# `uncheckedShiftL#` i'#) `or#`
                             (x# `uncheckedShiftRL#` (64# -# i'#)))
      where
        !i'# = word2Int# (int2Word# i# `and#` 63##)
    rotateR (W64# x#) (CountOf (I# i#))
        | isTrue# (i'# ==# 0#) = W64# x#
        | otherwise  = W64# ((x# `uncheckedShiftRL#` i'#) `or#`
                             (x# `uncheckedShiftL#` (64# -# i'#)))
      where
        !i'# = word2Int# (int2Word# i# `and#` 63##)
    bitFlip (W64# x#) = W64# (x# `xor#` mb#)
        where !(W64# mb#) = maxBound
    popCount (W64# x#) = CountOf $ wordToInt (W# (popCnt64# x#))
    countLeadingZeros (W64# w#) = CountOf $ wordToInt (W# (clz64# w#))
    countTrailingZeros (W64# w#) = CountOf $ wordToInt (W# (ctz64# w#))
instance BitOps Word64 where
    (W64# x#) .&. (W64# y#)   = W64# (x# `and#` y#)
    (W64# x#) .|. (W64# y#)   = W64# (x# `or#`  y#)
    (W64# x#) .^. (W64# y#)   = W64# (x# `xor#` y#)
    (W64# x#) .<<. (CountOf (I# i#)) = W64# (x# `shiftL#` i#)
    (W64# x#) .>>. (CountOf (I# i#)) = W64# (x# `shiftRL#` i#)
#else
instance FiniteBitsOps Word64 where
    numberOfBits :: Word64 -> CountOf Bool
numberOfBits _ = 64
    rotateL :: Word64 -> CountOf Bool -> Word64
rotateL (W64# x# :: Word64#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Word64# -> Word64
W64# Word64#
x#
        | Bool
otherwise  = Word64# -> Word64
W64# ((Word64#
x# Word64# -> Int# -> Word64#
`uncheckedShiftL64#` Int#
i'#) Word64# -> Word64# -> Word64#
`or64#`
                             (Word64#
x# Word64# -> Int# -> Word64#
`uncheckedShiftRL64#` (64# Int# -> Int# -> Int#
-# Int#
i'#)))
      where
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 63##)
    rotateR :: Word64 -> CountOf Bool -> Word64
rotateR (W64# x# :: Word64#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Word64# -> Word64
W64# Word64#
x#
        | Bool
otherwise  = Word64# -> Word64
W64# ((Word64#
x# Word64# -> Int# -> Word64#
`uncheckedShiftRL64#` Int#
i'#) Word64# -> Word64# -> Word64#
`or64#`
                             (Word64#
x# Word64# -> Int# -> Word64#
`uncheckedShiftL64#` (64# Int# -> Int# -> Int#
-# Int#
i'#)))
      where
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 63##)
    bitFlip :: Word64 -> Word64
bitFlip (W64# x# :: Word64#
x#) = Word64# -> Word64
W64# (Word64# -> Word64#
not64# Word64#
x#)
    popCount :: Word64 -> CountOf Bool
popCount (W64# x# :: Word64#
x#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word64# -> Word#
popCnt64# Word64#
x#))
    countLeadingZeros :: Word64 -> CountOf Bool
countLeadingZeros (W64# w# :: Word64#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word64# -> Word#
clz64# Word64#
w#))
    countTrailingZeros :: Word64 -> CountOf Bool
countTrailingZeros (W64# w# :: Word64#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word64# -> Word#
ctz64# Word64#
w#))
instance BitOps Word64 where
    (W64# x# :: Word64#
x#) .&. :: Word64 -> Word64 -> Word64
.&. (W64# y# :: Word64#
y#)   = Word64# -> Word64
W64# (Word64#
x# Word64# -> Word64# -> Word64#
`and64#` Word64#
y#)
    (W64# x# :: Word64#
x#) .|. :: Word64 -> Word64 -> Word64
.|. (W64# y# :: Word64#
y#)   = Word64# -> Word64
W64# (Word64#
x# Word64# -> Word64# -> Word64#
`or64#`  Word64#
y#)
    (W64# x# :: Word64#
x#) .^. :: Word64 -> Word64 -> Word64
.^. (W64# y# :: Word64#
y#)   = Word64# -> Word64
W64# (Word64#
x# Word64# -> Word64# -> Word64#
`xor64#` Word64#
y#)
    (W64# x# :: Word64#
x#) .<<. :: Word64 -> CountOf Bool -> Word64
.<<. (CountOf (I# i# :: Int#
i#)) = Word64# -> Word64
W64# (Word64#
x# Word64# -> Int# -> Word64#
`shiftL64#` Int#
i#)
    (W64# x# :: Word64#
x#) .>>. :: Word64 -> CountOf Bool -> Word64
.>>. (CountOf (I# i# :: Int#
i#)) = Word64# -> Word64
W64# (Word64#
x# Word64# -> Int# -> Word64#
`shiftRL64#` Int#
i#)

shiftL64#, shiftRL64# :: Word64# -> Int# -> Word64#
a :: Word64#
a shiftL64# :: Word64# -> Int# -> Word64#
`shiftL64#` b :: Int#
b  | Int# -> Bool
isTrue# (Int#
b Int# -> Int# -> Int#
>=# 64#) = Word# -> Word64#
wordToWord64# 0##
                 | Bool
otherwise           = Word64#
a Word64# -> Int# -> Word64#
`uncheckedShiftL64#` Int#
b
a :: Word64#
a shiftRL64# :: Word64# -> Int# -> Word64#
`shiftRL64#` b :: Int#
b | Int# -> Bool
isTrue# (Int#
b Int# -> Int# -> Int#
>=# 64#) = Word# -> Word64#
wordToWord64# 0##
                 | Bool
otherwise           = Word64#
a Word64# -> Int# -> Word64#
`uncheckedShiftRL64#` Int#
b
#endif

-- Word128 --------------------------------------------------------------------

instance FiniteBitsOps Word128 where
    numberOfBits :: Word128 -> CountOf Bool
numberOfBits _ = 128
    rotateL :: Word128 -> CountOf Bool -> Word128
rotateL w :: Word128
w (CountOf n :: Int
n) = Word128 -> Int -> Word128
Word128.rotateL Word128
w Int
n
    rotateR :: Word128 -> CountOf Bool -> Word128
rotateR w :: Word128
w (CountOf n :: Int
n) = Word128 -> Int -> Word128
Word128.rotateR Word128
w Int
n
    bitFlip :: Word128 -> Word128
bitFlip = Word128 -> Word128
Word128.complement
    popCount :: Word128 -> CountOf Bool
popCount = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool)
-> (Word128 -> Int) -> Word128 -> CountOf Bool
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Word128 -> Int
Word128.popCount
instance BitOps Word128 where
    .&. :: Word128 -> Word128 -> Word128
(.&.) = Word128 -> Word128 -> Word128
Word128.bitwiseAnd
    .|. :: Word128 -> Word128 -> Word128
(.|.) = Word128 -> Word128 -> Word128
Word128.bitwiseOr
    .^. :: Word128 -> Word128 -> Word128
(.^.) = Word128 -> Word128 -> Word128
Word128.bitwiseXor
    .<<. :: Word128 -> CountOf Bool -> Word128
(.<<.) w :: Word128
w (CountOf n :: Int
n) = Word128 -> Int -> Word128
Word128.shiftL Word128
w Int
n
    .>>. :: Word128 -> CountOf Bool -> Word128
(.>>.) w :: Word128
w (CountOf n :: Int
n) = Word128 -> Int -> Word128
Word128.shiftR Word128
w Int
n

-- Word256 --------------------------------------------------------------------

instance FiniteBitsOps Word256 where
    numberOfBits :: Word256 -> CountOf Bool
numberOfBits _ = 256
    rotateL :: Word256 -> CountOf Bool -> Word256
rotateL w :: Word256
w (CountOf n :: Int
n) = Word256 -> Int -> Word256
Word256.rotateL Word256
w Int
n
    rotateR :: Word256 -> CountOf Bool -> Word256
rotateR w :: Word256
w (CountOf n :: Int
n) = Word256 -> Int -> Word256
Word256.rotateR Word256
w Int
n
    bitFlip :: Word256 -> Word256
bitFlip = Word256 -> Word256
Word256.complement
    popCount :: Word256 -> CountOf Bool
popCount = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool)
-> (Word256 -> Int) -> Word256 -> CountOf Bool
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Word256 -> Int
Word256.popCount
instance BitOps Word256 where
    .&. :: Word256 -> Word256 -> Word256
(.&.) = Word256 -> Word256 -> Word256
Word256.bitwiseAnd
    .|. :: Word256 -> Word256 -> Word256
(.|.) = Word256 -> Word256 -> Word256
Word256.bitwiseOr
    .^. :: Word256 -> Word256 -> Word256
(.^.) = Word256 -> Word256 -> Word256
Word256.bitwiseXor
    .<<. :: Word256 -> CountOf Bool -> Word256
(.<<.) w :: Word256
w (CountOf n :: Int
n) = Word256 -> Int -> Word256
Word256.shiftL Word256
w Int
n
    .>>. :: Word256 -> CountOf Bool -> Word256
(.>>.) w :: Word256
w (CountOf n :: Int
n) = Word256 -> Int -> Word256
Word256.shiftR Word256
w Int
n

-- Int8 -----------------------------------------------------------------------

instance FiniteBitsOps Int8 where
    numberOfBits :: Int8 -> CountOf Bool
numberOfBits _ = 8
    rotateL :: Int8 -> CountOf Bool -> Int8
rotateL (I8# x# :: Int#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Int# -> Int8
I8# Int#
x#
        | Bool
otherwise  = Int# -> Int8
I8# (Int# -> Int#
narrow8Int# (Word# -> Int#
word2Int# ((Word#
x'# Word# -> Int# -> Word#
`uncheckedShiftL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
                                                    (Word#
x'# Word# -> Int# -> Word#
`uncheckedShiftRL#` (8# Int# -> Int# -> Int#
-# Int#
i'#)))))
      where
        !x'# :: Word#
x'# = Word# -> Word#
narrow8Word# (Int# -> Word#
int2Word# Int#
x#)
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 7##)
    rotateR :: Int8 -> CountOf Bool -> Int8
rotateR (I8# x# :: Int#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Int# -> Int8
I8# Int#
x#
        | Bool
otherwise  = Int# -> Int8
I8# (Int# -> Int#
narrow8Int# (Word# -> Int#
word2Int# ((Word#
x'# Word# -> Int# -> Word#
`uncheckedShiftRL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
                                                    (Word#
x'# Word# -> Int# -> Word#
`uncheckedShiftL#` (8# Int# -> Int# -> Int#
-# Int#
i'#)))))
      where
        !x'# :: Word#
x'# = Word# -> Word#
narrow8Word# (Int# -> Word#
int2Word# Int#
x#)
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 7##)
    bitFlip :: Int8 -> Int8
bitFlip (I8# x# :: Int#
x#) = Int# -> Int8
I8# (Word# -> Int#
word2Int# (Word# -> Word#
not# (Int# -> Word#
int2Word# Int#
x#)))
    popCount :: Int8 -> CountOf Bool
popCount (I8# x# :: Int#
x#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
popCnt8# (Int# -> Word#
int2Word# Int#
x#)))
    countLeadingZeros :: Int8 -> CountOf Bool
countLeadingZeros (I8# w# :: Int#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
clz8# (Int# -> Word#
int2Word# Int#
w#)))
    countTrailingZeros :: Int8 -> CountOf Bool
countTrailingZeros (I8# w# :: Int#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
ctz8# (Int# -> Word#
int2Word# Int#
w#)))
instance BitOps Int8 where
    (I8# x# :: Int#
x#) .&. :: Int8 -> Int8 -> Int8
.&. (I8# y# :: Int#
y#)   = Int# -> Int8
I8# (Int#
x# Int# -> Int# -> Int#
`andI#` Int#
y#)
    (I8# x# :: Int#
x#) .|. :: Int8 -> Int8 -> Int8
.|. (I8# y# :: Int#
y#)   = Int# -> Int8
I8# (Int#
x# Int# -> Int# -> Int#
`orI#`  Int#
y#)
    (I8# x# :: Int#
x#) .^. :: Int8 -> Int8 -> Int8
.^. (I8# y# :: Int#
y#)   = Int# -> Int8
I8# (Int#
x# Int# -> Int# -> Int#
`xorI#` Int#
y#)
    (I8# x# :: Int#
x#) .<<. :: Int8 -> CountOf Bool -> Int8
.<<. (CountOf (I# i# :: Int#
i#)) = Int# -> Int8
I8# (Int# -> Int#
narrow8Int# (Int#
x# Int# -> Int# -> Int#
`iShiftL#`  Int#
i#))
    (I8# x# :: Int#
x#) .>>. :: Int8 -> CountOf Bool -> Int8
.>>. (CountOf (I# i# :: Int#
i#)) = Int# -> Int8
I8# (Int# -> Int#
narrow8Int# (Int#
x# Int# -> Int# -> Int#
`iShiftRL#` Int#
i#))

-- Int16 ----------------------------------------------------------------------

instance FiniteBitsOps Int16 where
    numberOfBits :: Int16 -> CountOf Bool
numberOfBits _ = 16
    rotateL :: Int16 -> CountOf Bool -> Int16
rotateL (I16# x# :: Int#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Int# -> Int16
I16# Int#
x#
        | Bool
otherwise  = Int# -> Int16
I16# (Int# -> Int#
narrow16Int# (Word# -> Int#
word2Int# ((Word#
x'# Word# -> Int# -> Word#
`uncheckedShiftL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
                                                      (Word#
x'# Word# -> Int# -> Word#
`uncheckedShiftRL#` (16# Int# -> Int# -> Int#
-# Int#
i'#)))))
      where
        !x'# :: Word#
x'# = Word# -> Word#
narrow16Word# (Int# -> Word#
int2Word# Int#
x#)
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 15##)
    rotateR :: Int16 -> CountOf Bool -> Int16
rotateR (I16# x# :: Int#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Int# -> Int16
I16# Int#
x#
        | Bool
otherwise  = Int# -> Int16
I16# (Int# -> Int#
narrow16Int# (Word# -> Int#
word2Int# ((Word#
x'# Word# -> Int# -> Word#
`uncheckedShiftRL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
                                                      (Word#
x'# Word# -> Int# -> Word#
`uncheckedShiftL#` (16# Int# -> Int# -> Int#
-# Int#
i'#)))))
      where
        !x'# :: Word#
x'# = Word# -> Word#
narrow16Word# (Int# -> Word#
int2Word# Int#
x#)
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 15##)
    bitFlip :: Int16 -> Int16
bitFlip (I16# x# :: Int#
x#) = Int# -> Int16
I16# (Word# -> Int#
word2Int# (Word# -> Word#
not# (Int# -> Word#
int2Word# Int#
x#)))
    popCount :: Int16 -> CountOf Bool
popCount (I16# x# :: Int#
x#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
popCnt16# (Int# -> Word#
int2Word# Int#
x#)))
    countLeadingZeros :: Int16 -> CountOf Bool
countLeadingZeros (I16# w# :: Int#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
clz16# (Int# -> Word#
int2Word# Int#
w#)))
    countTrailingZeros :: Int16 -> CountOf Bool
countTrailingZeros (I16# w# :: Int#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
ctz16# (Int# -> Word#
int2Word# Int#
w#)))
instance BitOps Int16 where
    (I16# x# :: Int#
x#) .&. :: Int16 -> Int16 -> Int16
.&. (I16# y# :: Int#
y#)   = Int# -> Int16
I16# (Int#
x# Int# -> Int# -> Int#
`andI#` Int#
y#)
    (I16# x# :: Int#
x#) .|. :: Int16 -> Int16 -> Int16
.|. (I16# y# :: Int#
y#)   = Int# -> Int16
I16# (Int#
x# Int# -> Int# -> Int#
`orI#`  Int#
y#)
    (I16# x# :: Int#
x#) .^. :: Int16 -> Int16 -> Int16
.^. (I16# y# :: Int#
y#)   = Int# -> Int16
I16# (Int#
x# Int# -> Int# -> Int#
`xorI#` Int#
y#)
    (I16# x# :: Int#
x#) .<<. :: Int16 -> CountOf Bool -> Int16
.<<. (CountOf (I# i# :: Int#
i#)) = Int# -> Int16
I16# (Int# -> Int#
narrow16Int# (Int#
x# Int# -> Int# -> Int#
`iShiftL#`  Int#
i#))
    (I16# x# :: Int#
x#) .>>. :: Int16 -> CountOf Bool -> Int16
.>>. (CountOf (I# i# :: Int#
i#)) = Int# -> Int16
I16# (Int# -> Int#
narrow16Int# (Int#
x# Int# -> Int# -> Int#
`iShiftRL#` Int#
i#))

-- Int32 ----------------------------------------------------------------------

instance FiniteBitsOps Int32 where
    numberOfBits :: Int32 -> CountOf Bool
numberOfBits _ = 32
    rotateL :: Int32 -> CountOf Bool -> Int32
rotateL (I32# x# :: Int#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Int# -> Int32
I32# Int#
x#
        | Bool
otherwise  = Int# -> Int32
I32# (Int# -> Int#
narrow32Int# (Word# -> Int#
word2Int# ((Word#
x'# Word# -> Int# -> Word#
`uncheckedShiftL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
                                                      (Word#
x'# Word# -> Int# -> Word#
`uncheckedShiftRL#` (32# Int# -> Int# -> Int#
-# Int#
i'#)))))
      where
        !x'# :: Word#
x'# = Word# -> Word#
narrow32Word# (Int# -> Word#
int2Word# Int#
x#)
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 31##)
    rotateR :: Int32 -> CountOf Bool -> Int32
rotateR (I32# x# :: Int#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Int# -> Int32
I32# Int#
x#
        | Bool
otherwise  = Int# -> Int32
I32# (Int# -> Int#
narrow32Int# (Word# -> Int#
word2Int# ((Word#
x'# Word# -> Int# -> Word#
`uncheckedShiftRL#` Int#
i'#) Word# -> Word# -> Word#
`or#`
                                                      (Word#
x'# Word# -> Int# -> Word#
`uncheckedShiftL#` (32# Int# -> Int# -> Int#
-# Int#
i'#)))))
      where
        !x'# :: Word#
x'# = Word# -> Word#
narrow32Word# (Int# -> Word#
int2Word# Int#
x#)
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 31##)
    bitFlip :: Int32 -> Int32
bitFlip (I32# x# :: Int#
x#) = Int# -> Int32
I32# (Word# -> Int#
word2Int# (Word# -> Word#
not# (Int# -> Word#
int2Word# Int#
x#)))
    popCount :: Int32 -> CountOf Bool
popCount (I32# x# :: Int#
x#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
popCnt32# (Int# -> Word#
int2Word# Int#
x#)))
    countLeadingZeros :: Int32 -> CountOf Bool
countLeadingZeros (I32# w# :: Int#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
clz32# (Int# -> Word#
int2Word# Int#
w#)))
    countTrailingZeros :: Int32 -> CountOf Bool
countTrailingZeros (I32# w# :: Int#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word# -> Word#
ctz32# (Int# -> Word#
int2Word# Int#
w#)))
instance BitOps Int32 where
    (I32# x# :: Int#
x#) .&. :: Int32 -> Int32 -> Int32
.&. (I32# y# :: Int#
y#)   = Int# -> Int32
I32# (Int#
x# Int# -> Int# -> Int#
`andI#` Int#
y#)
    (I32# x# :: Int#
x#) .|. :: Int32 -> Int32 -> Int32
.|. (I32# y# :: Int#
y#)   = Int# -> Int32
I32# (Int#
x# Int# -> Int# -> Int#
`orI#`  Int#
y#)
    (I32# x# :: Int#
x#) .^. :: Int32 -> Int32 -> Int32
.^. (I32# y# :: Int#
y#)   = Int# -> Int32
I32# (Int#
x# Int# -> Int# -> Int#
`xorI#` Int#
y#)
    (I32# x# :: Int#
x#) .<<. :: Int32 -> CountOf Bool -> Int32
.<<. (CountOf (I# i# :: Int#
i#)) = Int# -> Int32
I32# (Int# -> Int#
narrow32Int# (Int#
x# Int# -> Int# -> Int#
`iShiftL#`  Int#
i#))
    (I32# x# :: Int#
x#) .>>. :: Int32 -> CountOf Bool -> Int32
.>>. (CountOf (I# i# :: Int#
i#)) = Int# -> Int32
I32# (Int# -> Int#
narrow32Int# (Int#
x# Int# -> Int# -> Int#
`iShiftRL#` Int#
i#))

-- Int64 ----------------------------------------------------------------------

#if WORD_SIZE_IN_BITS == 64
instance FiniteBitsOps Int64 where
    numberOfBits _ = 64
    rotateL (I64# x#) (CountOf (I# i#))
        | isTrue# (i'# ==# 0#) = I64# x#
        | otherwise  = I64# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
                                        (x'# `uncheckedShiftRL#` (64# -# i'#))))
      where
        !x'# = int2Word# x#
        !i'# = word2Int# (int2Word# i# `and#` 63##)
    rotateR (I64# x#) (CountOf (I# i#))
        | isTrue# (i'# ==# 0#) = I64# x#
        | otherwise  = I64# (word2Int# ((x'# `uncheckedShiftRL#` i'#) `or#`
                                        (x'# `uncheckedShiftL#` (64# -# i'#))))
      where
        !x'# = int2Word# x#
        !i'# = word2Int# (int2Word# i# `and#` 63##)
    bitFlip (I64# x#) = I64# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
    popCount (I64# x#) = CountOf $ wordToInt (W# (popCnt64# (int2Word# x#)))
    countLeadingZeros (I64# w#) = CountOf $ wordToInt (W# (clz64# (int2Word# w#)))
    countTrailingZeros (I64# w#) = CountOf $ wordToInt (W# (ctz64# (int2Word# w#)))
instance BitOps Int64 where
    (I64# x#) .&. (I64# y#)   = I64# (x# `andI#` y#)
    (I64# x#) .|. (I64# y#)   = I64# (x# `orI#`  y#)
    (I64# x#) .^. (I64# y#)   = I64# (x# `xorI#` y#)
    (I64# x#) .<<. (CountOf (I# w#)) = I64# (x# `iShiftL#`  w#)
    (I64# x#) .>>. (CountOf (I# w#)) = I64# (x# `iShiftRL#` w#)
#else
instance FiniteBitsOps Int64 where
    numberOfBits :: Int64 -> CountOf Bool
numberOfBits _ = 64
    rotateL :: Int64 -> CountOf Bool -> Int64
rotateL (I64# x# :: Int64#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Int64# -> Int64
I64# Int64#
x#
        | Bool
otherwise  = Int64# -> Int64
I64# (Word64# -> Int64#
word64ToInt64# ((Word64#
x'# Word64# -> Int# -> Word64#
`uncheckedShiftL64#` Int#
i'#) Word64# -> Word64# -> Word64#
`or64#`
                                             (Word64#
x'# Word64# -> Int# -> Word64#
`uncheckedShiftRL64#` (64# Int# -> Int# -> Int#
-# Int#
i'#))))
      where
        !x'# :: Word64#
x'# = Int64# -> Word64#
int64ToWord64# Int64#
x#
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 63##)
    rotateR :: Int64 -> CountOf Bool -> Int64
rotateR (I64# x# :: Int64#
x#) (CountOf (I# i# :: Int#
i#))
        | Int# -> Bool
isTrue# (Int#
i'# Int# -> Int# -> Int#
==# 0#) = Int64# -> Int64
I64# Int64#
x#
        | Bool
otherwise  = Int64# -> Int64
I64# (Word64# -> Int64#
word64ToInt64# ((Word64#
x'# Word64# -> Int# -> Word64#
`uncheckedShiftRL64#` Int#
i'#) Word64# -> Word64# -> Word64#
`or64#`
                                             (Word64#
x'# Word64# -> Int# -> Word64#
`uncheckedShiftL64#` (64# Int# -> Int# -> Int#
-# Int#
i'#))))
      where
        !x'# :: Word64#
x'# = Int64# -> Word64#
int64ToWord64# Int64#
x#
        !i'# :: Int#
i'# = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
`and#` 63##)
    bitFlip :: Int64 -> Int64
bitFlip (I64# x# :: Int64#
x#) = Int64# -> Int64
I64# (Word64# -> Int64#
word64ToInt64# (Word64# -> Word64#
not64# (Int64# -> Word64#
int64ToWord64# Int64#
x#)))
    popCount :: Int64 -> CountOf Bool
popCount (I64# x# :: Int64#
x#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word64# -> Word#
popCnt64# (Int64# -> Word64#
int64ToWord64# Int64#
x#)))
    countLeadingZeros :: Int64 -> CountOf Bool
countLeadingZeros (I64# w# :: Int64#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word64# -> Word#
clz64# (Int64# -> Word64#
int64ToWord64# Int64#
w#)))
    countTrailingZeros :: Int64 -> CountOf Bool
countTrailingZeros (I64# w# :: Int64#
w#) = Int -> CountOf Bool
forall ty. Int -> CountOf ty
CountOf (Int -> CountOf Bool) -> Int -> CountOf Bool
forall a b. (a -> b) -> a -> b
$ Word -> Int
wordToInt (Word# -> Word
W# (Word64# -> Word#
ctz64# (Int64# -> Word64#
int64ToWord64# Int64#
w#)))
instance BitOps Int64 where
    (I64# x# :: Int64#
x#) .&. :: Int64 -> Int64 -> Int64
.&. (I64# y# :: Int64#
y#)  = Int64# -> Int64
I64# (Word64# -> Int64#
word64ToInt64# (Int64# -> Word64#
int64ToWord64# Int64#
x# Word64# -> Word64# -> Word64#
`and64#` Int64# -> Word64#
int64ToWord64# Int64#
y#))
    (I64# x# :: Int64#
x#) .|. :: Int64 -> Int64 -> Int64
.|. (I64# y# :: Int64#
y#)  = Int64# -> Int64
I64# (Word64# -> Int64#
word64ToInt64# (Int64# -> Word64#
int64ToWord64# Int64#
x# Word64# -> Word64# -> Word64#
`or64#`  Int64# -> Word64#
int64ToWord64# Int64#
y#))
    (I64# x# :: Int64#
x#) .^. :: Int64 -> Int64 -> Int64
.^. (I64# y# :: Int64#
y#)  = Int64# -> Int64
I64# (Word64# -> Int64#
word64ToInt64# (Int64# -> Word64#
int64ToWord64# Int64#
x# Word64# -> Word64# -> Word64#
`xor64#` Int64# -> Word64#
int64ToWord64# Int64#
y#))
    (I64# x# :: Int64#
x#) .<<. :: Int64 -> CountOf Bool -> Int64
.<<. (CountOf (I# w# :: Int#
w#)) = Int64# -> Int64
I64# (Int64#
x# Int64# -> Int# -> Int64#
`iShiftL64#`  Int#
w#)
    (I64# x# :: Int64#
x#) .>>. :: Int64 -> CountOf Bool -> Int64
.>>. (CountOf (I# w# :: Int#
w#)) = Int64# -> Int64
I64# (Int64#
x# Int64# -> Int# -> Int64#
`iShiftRA64#` Int#
w#)


iShiftL64#, iShiftRA64# :: Int64# -> Int# -> Int64#
a :: Int64#
a iShiftL64# :: Int64# -> Int# -> Int64#
`iShiftL64#` b :: Int#
b  | Int# -> Bool
isTrue# (Int#
b Int# -> Int# -> Int#
>=# 64#) = Int# -> Int64#
intToInt64# 0#
                  | Bool
otherwise           = Int64#
a Int64# -> Int# -> Int64#
`uncheckedIShiftL64#` Int#
b
a :: Int64#
a iShiftRA64# :: Int64# -> Int# -> Int64#
`iShiftRA64#` b :: Int#
b | Int# -> Bool
isTrue# (Int#
b Int# -> Int# -> Int#
>=# 64#) Bool -> Bool -> Bool
&& Int# -> Bool
isTrue# (Int64#
a Int64# -> Int64# -> Int#
`ltInt64#` (Int# -> Int64#
intToInt64# 0#))
                                        = Int# -> Int64#
intToInt64# (-1#)
                  | Int# -> Bool
isTrue# (Int#
b Int# -> Int# -> Int#
>=# 64#) = Int# -> Int64#
intToInt64# 0#
                  | Bool
otherwise = Int64#
a Int64# -> Int# -> Int64#
`uncheckedIShiftRA64#` Int#
b

#endif