{-# LANGUAGE CPP #-}
#ifdef __GLASGOW_HASKELL__
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE Trustworthy #-}
#endif
#include "containers.h"
module Utils.Containers.Internal.BitUtil
( shiftLL
, shiftRL
, wordSize
, iShiftRL
) where
import Data.Bits (unsafeShiftL, unsafeShiftR, finiteBitSize)
#ifdef __GLASGOW_HASKELL__
import GHC.Exts (Int(..), uncheckedIShiftRL#)
#endif
shiftRL, shiftLL :: Word -> Int -> Word
shiftRL :: Word -> Int -> Word
shiftRL = Word -> Int -> Word
forall a. Bits a => a -> Int -> a
unsafeShiftR
shiftLL :: Word -> Int -> Word
shiftLL = Word -> Int -> Word
forall a. Bits a => a -> Int -> a
unsafeShiftL
{-# INLINE wordSize #-}
wordSize :: Int
wordSize :: Int
wordSize = Word -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize (Word
0 :: Word)
iShiftRL :: Int -> Int -> Int
#ifdef __GLASGOW_HASKELL__
iShiftRL :: Int -> Int -> Int
iShiftRL (I# Int#
x#) (I# Int#
sh#) = Int# -> Int
I# (Int# -> Int# -> Int#
uncheckedIShiftRL# Int#
x# Int#
sh#)
#else
iShiftRL x sh = fromIntegral (unsafeShiftR (fromIntegral x :: Word) sh)
#endif