(original) (raw)

{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE Trustworthy #-}

{-# OPTIONS_HADDOCK not-home #-}

module GHC.Bits ( Bits( (.&.), (.|.), xor, complement, shift, rotate, zeroBits, bit, setBit, clearBit, complementBit, testBit, bitSizeMaybe, bitSize, isSigned, shiftL, shiftR, unsafeShiftL, unsafeShiftR, rotateL, rotateR, popCount ), FiniteBits( finiteBitSize, countLeadingZeros, countTrailingZeros ),

bitDefault, testBitDefault, popCountDefault, toIntegralSized, ) where

#include "MachDeps.h"

import Data.Maybe import GHC.Num import GHC.Base import GHC.Real

infixl 8 shift, rotate, shiftL, shiftR, rotateL, rotateR infixl 7 .&. infixl 6 xor infixl 5 .|.

{-# DEPRECATED bitSize "Use 'bitSizeMaybe' or 'finiteBitSize' instead" #-}

class Eq a => Bits a where {-# MINIMAL (.&.), (.|.), xor, complement, (shift | (shiftL, shiftR)), (rotate | (rotateL, rotateR)), bitSize, bitSizeMaybe, isSigned, testBit, bit, popCount #-}

[(.&.)](GHC.Bits.html#.%26.) :: [a](#local-6989586621679584573) -> [a](#local-6989586621679584573) -> [a](#local-6989586621679584573)


[(.|.)](GHC.Bits.html#.%7C.) :: [a](#local-6989586621679584573) -> [a](#local-6989586621679584573) -> [a](#local-6989586621679584573)


[xor](GHC.Bits.html#xor) :: [a](#local-6989586621679584573) -> [a](#local-6989586621679584573) -> [a](#local-6989586621679584573)


[complement](GHC.Bits.html#complement)        :: [a](#local-6989586621679584573) -> [a](#local-6989586621679584573)


[shift](GHC.Bits.html#shift)             :: [a](#local-6989586621679584573) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int) -> [a](#local-6989586621679584573)

a

x shift Int i | Int iInt -> Int -> Bool forall a. Ord a => a -> a -> Bool <Int 0 = a x a -> Int -> a forall a. Bits a => a -> Int -> a shiftR (-Int i) | Int iInt -> Int -> Bool forall a. Ord a => a -> a -> Bool >Int 0 = a x a -> Int -> a forall a. Bits a => a -> Int -> a shiftL Int i | Bool otherwise = a x

[rotate](GHC.Bits.html#rotate)            :: [a](#local-6989586621679584573) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int) -> [a](#local-6989586621679584573)

a

x rotate Int i | Int iInt -> Int -> Bool forall a. Ord a => a -> a -> Bool <Int 0 = a x a -> Int -> a forall a. Bits a => a -> Int -> a rotateR (-Int i) | Int iInt -> Int -> Bool forall a. Ord a => a -> a -> Bool >Int 0 = a x a -> Int -> a forall a. Bits a => a -> Int -> a rotateL Int i | Bool otherwise = a x

[zeroBits](GHC.Bits.html#zeroBits) :: [a](#local-6989586621679584573)
[zeroBits](GHC.Bits.html#zeroBits) = a -> Int -> a

forall a. Bits a => a -> Int -> a clearBit (Int -> a forall a. Bits a => Int -> a bit Int 0) Int 0

[bit](GHC.Bits.html#bit)               :: [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int) -> [a](#local-6989586621679584573)


[setBit](GHC.Bits.html#setBit)            :: [a](#local-6989586621679584573) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int) -> [a](#local-6989586621679584573)


[clearBit](GHC.Bits.html#clearBit)          :: [a](#local-6989586621679584573) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int) -> [a](#local-6989586621679584573)


[complementBit](GHC.Bits.html#complementBit)     :: [a](#local-6989586621679584573) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int) -> [a](#local-6989586621679584573)


[testBit](GHC.Bits.html#testBit)           :: [a](#local-6989586621679584573) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int) -> [Bool](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Bool/GHC.Types.html#Bool)


[bitSizeMaybe](GHC.Bits.html#bitSizeMaybe)      :: [a](#local-6989586621679584573) -> [Maybe](GHC.Maybe.html#Maybe) [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int)


[bitSize](GHC.Bits.html#bitSize)           :: [a](#local-6989586621679584573) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int)
[bitSize](GHC.Bits.html#bitSize) a

b = Int -> Maybe Int -> Int forall a. a -> Maybe a -> a fromMaybe ([Char] -> Int forall a. HasCallStack => [Char] -> a error [Char] "bitSize is undefined") (a -> Maybe Int forall a. Bits a => a -> Maybe Int bitSizeMaybe a b)

[isSigned](GHC.Bits.html#isSigned)          :: [a](#local-6989586621679584573) -> [Bool](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Bool/GHC.Types.html#Bool)

{-# INLINE [setBit](GHC.Bits.html#setBit) #-}
{-# INLINE [clearBit](GHC.Bits.html#clearBit) #-}
{-# INLINE [complementBit](GHC.Bits.html#complementBit) #-}
a

x setBit Int i = a x a -> a -> a forall a. Bits a => a -> a -> a .|. Int -> a forall a. Bits a => Int -> a bit Int i a x clearBit Int i = a x a -> a -> a forall a. Bits a => a -> a -> a .&. a -> a forall a. Bits a => a -> a complement (Int -> a forall a. Bits a => Int -> a bit Int i) a x complementBit Int i = a x a -> a -> a forall a. Bits a => a -> a -> a xor Int -> a forall a. Bits a => Int -> a bit Int i

[shiftL](GHC.Bits.html#shiftL)            :: [a](#local-6989586621679584573) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int) -> [a](#local-6989586621679584573)
{-# INLINE [shiftL](GHC.Bits.html#shiftL) #-}
a

x shiftL Int i = a x a -> Int -> a forall a. Bits a => a -> Int -> a shift Int i

[unsafeShiftL](GHC.Bits.html#unsafeShiftL)            :: [a](#local-6989586621679584573) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int) -> [a](#local-6989586621679584573)
{-# INLINE [unsafeShiftL](GHC.Bits.html#unsafeShiftL) #-}
a

x unsafeShiftL Int i = a x a -> Int -> a forall a. Bits a => a -> Int -> a shiftL Int i

[shiftR](GHC.Bits.html#shiftR)            :: [a](#local-6989586621679584573) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int) -> [a](#local-6989586621679584573)
{-# INLINE [shiftR](GHC.Bits.html#shiftR) #-}
a

x shiftR Int i = a x a -> Int -> a forall a. Bits a => a -> Int -> a shift (-Int i)

[unsafeShiftR](GHC.Bits.html#unsafeShiftR)            :: [a](#local-6989586621679584573) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int) -> [a](#local-6989586621679584573)
{-# INLINE [unsafeShiftR](GHC.Bits.html#unsafeShiftR) #-}
a

x unsafeShiftR Int i = a x a -> Int -> a forall a. Bits a => a -> Int -> a shiftR Int i

[rotateL](GHC.Bits.html#rotateL)           :: [a](#local-6989586621679584573) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int) -> [a](#local-6989586621679584573)
{-# INLINE [rotateL](GHC.Bits.html#rotateL) #-}
a

x rotateL Int i = a x a -> Int -> a forall a. Bits a => a -> Int -> a rotate Int i

[rotateR](GHC.Bits.html#rotateR)           :: [a](#local-6989586621679584573) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int) -> [a](#local-6989586621679584573)
{-# INLINE [rotateR](GHC.Bits.html#rotateR) #-}
a

x rotateR Int i = a x a -> Int -> a forall a. Bits a => a -> Int -> a rotate (-Int i)

[popCount](GHC.Bits.html#popCount)          :: [a](#local-6989586621679584573) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int)

class Bits b => FiniteBits b where

[finiteBitSize](GHC.Bits.html#finiteBitSize) :: [b](#local-6989586621679584580) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int)


[countLeadingZeros](GHC.Bits.html#countLeadingZeros) :: [b](#local-6989586621679584580) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int)
[countLeadingZeros](GHC.Bits.html#countLeadingZeros) b

x = (Int wInt -> Int -> Int forall a. Num a => a -> a -> a -Int

  1. Int -> Int -> Int forall a. Num a => a -> a -> a - Int -> Int go (Int wInt -> Int -> Int forall a. Num a => a -> a -> a -Int
  2. where
      go :: Int -> Int

go Int i | Int i Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int 0 = Int i | b -> Int -> Bool forall a. Bits a => a -> Int -> Bool testBit b x Int i = Int i | Bool otherwise = Int -> Int go (Int iInt -> Int -> Int forall a. Num a => a -> a -> a -Int 1)

    w :: Int

w = b -> Int forall b. FiniteBits b => b -> Int finiteBitSize b x

[countTrailingZeros](GHC.Bits.html#countTrailingZeros) :: [b](#local-6989586621679584580) -> [Int](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#Int/GHC.Types.html#Int)
[countTrailingZeros](GHC.Bits.html#countTrailingZeros) b

x = Int -> Int go Int 0 where go :: Int -> Int go Int i | Int i Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >= Int w = Int i | b -> Int -> Bool forall a. Bits a => a -> Int -> Bool testBit b x Int i = Int i | Bool otherwise = Int -> Int go (Int iInt -> Int -> Int forall a. Num a => a -> a -> a +Int 1)

    w :: Int

w = b -> Int forall b. FiniteBits b => b -> Int finiteBitSize b x

bitDefault :: (Bits a, Num a) => Int -> a bitDefault :: forall a. (Bits a, Num a) => Int -> a bitDefault = \Int i -> a 1 a -> Int -> a forall a. Bits a => a -> Int -> a shiftL Int i {-# INLINE bitDefault #-}

testBitDefault :: (Bits a, Num a) => a -> Int -> Bool testBitDefault :: forall a. (Bits a, Num a) => a -> Int -> Bool testBitDefault = \a x Int i -> (a x a -> a -> a forall a. Bits a => a -> a -> a .&. Int -> a forall a. Bits a => Int -> a bit Int i) a -> a -> Bool forall a. Eq a => a -> a -> Bool /= a 0 {-# INLINE testBitDefault #-}

popCountDefault :: (Bits a, Num a) => a -> Int popCountDefault :: forall a. (Bits a, Num a) => a -> Int popCountDefault = Int -> a -> Int forall {t} {t}. (Num t, Num t, Bits t) => t -> t -> t go Int 0 where go :: t -> t -> t go !t c t 0 = t c go t c t w = t -> t -> t go (t ct -> t -> t forall a. Num a => a -> a -> a +t

  1. (t w t -> t -> t forall a. Bits a => a -> a -> a .&. (t w t -> t -> t forall a. Num a => a -> a -> a - t 1)) {-# INLINABLE popCountDefault #-}

instance Bits Bool where .&. :: Bool -> Bool -> Bool (.&.) = Bool -> Bool -> Bool (&&)

.|. :: Bool -> Bool -> Bool

(.|.) = Bool -> Bool -> Bool (||)

xor :: Bool -> Bool -> Bool

xor = Bool -> Bool -> Bool forall a. Eq a => a -> a -> Bool (/=)

complement :: Bool -> Bool

complement = Bool -> Bool not

shift :: Bool -> Int -> Bool

shift Bool x Int 0 = Bool x shift Bool _ Int _ = Bool False

rotate :: Bool -> Int -> Bool

rotate Bool x Int _ = Bool x

bit :: Int -> Bool

bit Int 0 = Bool True bit Int _ = Bool False

testBit :: Bool -> Int -> Bool

testBit Bool x Int 0 = Bool x testBit Bool _ Int _ = Bool False

bitSizeMaybe :: Bool -> Maybe Int

bitSizeMaybe Bool _ = Int -> Maybe Int forall a. a -> Maybe a Just Int 1

bitSize :: Bool -> Int

bitSize Bool _ = Int 1

isSigned :: Bool -> Bool

isSigned Bool _ = Bool False

popCount :: Bool -> Int

popCount Bool False = Int 0 popCount Bool True = Int 1

instance FiniteBits Bool where finiteBitSize :: Bool -> Int finiteBitSize Bool _ = Int 1 countTrailingZeros :: Bool -> Int countTrailingZeros Bool x = if Bool x then Int 0 else Int 1 countLeadingZeros :: Bool -> Int countLeadingZeros Bool x = if Bool x then Int 0 else Int 1

instance Bits Int where {-# INLINE shift #-} {-# INLINE bit #-} {-# INLINE testBit #-}

{-# INLINE [popCount](GHC.Bits.html#popCount) #-}

zeroBits :: Int

zeroBits = Int 0

bit :: Int -> Int

bit = Int -> Int forall a. (Bits a, Num a) => Int -> a bitDefault

testBit :: Int -> Int -> Bool

testBit = Int -> Int -> Bool forall a. (Bits a, Num a) => a -> Int -> Bool testBitDefault

([I#](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#I%23/GHC.Types.html#I%23) Int#

x#) .&. :: Int -> Int -> Int .&. (I# Int# y#) = Int# -> Int I# (Int# x# Int# -> Int# -> Int# andI# Int# y#) (I# Int# x#) .|. :: Int -> Int -> Int .|. (I# Int# y#) = Int# -> Int I# (Int# x# Int# -> Int# -> Int# orI# Int# y#) (I# Int# x#) xor :: Int -> Int -> Int xor (I# Int# y#) = Int# -> Int I# (Int# x# Int# -> Int# -> Int# xorI# Int# y#) complement :: Int -> Int complement (I# Int# x#) = Int# -> Int I# (Int# -> Int# notI# Int# x#) (I# Int# x#) shift :: Int -> Int -> Int shift (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int# -> Int I# (Int# x# Int# -> Int# -> Int# iShiftL# Int# i#) | Bool otherwise = Int# -> Int I# (Int# x# Int# -> Int# -> Int# iShiftRA# Int# -> Int# negateInt# Int# i#) (I# Int# x#) shiftL :: Int -> Int -> Int shiftL (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int# -> Int I# (Int# x# Int# -> Int# -> Int# iShiftL# Int# i#) | Bool otherwise = Int forall a. a overflowError (I# Int# x#) unsafeShiftL :: Int -> Int -> Int unsafeShiftL (I# Int# i#) = Int# -> Int I# (Int# x# Int# -> Int# -> Int# uncheckedIShiftL# Int# i#) (I# Int# x#) shiftR :: Int -> Int -> Int shiftR (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Int# -> Int I# (Int# x# Int# -> Int# -> Int# iShiftRA# Int# i#) | Bool otherwise = Int forall a. a overflowError (I# Int# x#) unsafeShiftR :: Int -> Int -> Int unsafeShiftR (I# Int# i#) = Int# -> Int I# (Int# x# Int# -> Int# -> Int# uncheckedIShiftRA# Int# i#)

{-# INLINE [rotate](GHC.Bits.html#rotate) #-}       
([I#](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#I%23/GHC.Types.html#I%23) Int#

x#) rotate :: Int -> Int -> Int rotate (I# Int# i#) = Int# -> Int I# ((Int# x# Int# -> Int# -> Int# uncheckedIShiftL# Int# i'#) Int# -> Int# -> Int# orI# (Int# x# Int# -> Int# -> Int# uncheckedIShiftRL# (Int# wsib Int# -> Int# -> Int# -# Int# i'#))) where !i'# :: Int# i'# = Int# i# Int# -> Int# -> Int# andI# (Int# wsib Int# -> Int# -> Int# -# Int# 1#) !wsib :: Int# wsib = WORD_SIZE_IN_BITS#
bitSizeMaybe :: Int -> Maybe Int bitSizeMaybe Int i = Int -> Maybe Int forall a. a -> Maybe a Just (Int -> Int forall b. FiniteBits b => b -> Int finiteBitSize Int i) bitSize :: Int -> Int bitSize Int i = Int -> Int forall b. FiniteBits b => b -> Int finiteBitSize Int i

popCount :: Int -> Int

popCount (I# Int# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# popCnt# (Int# -> Word# int2Word# Int# x#)))

isSigned :: Int -> Bool

isSigned Int _ = Bool True

instance FiniteBits Int where finiteBitSize :: Int -> Int finiteBitSize Int _ = WORD_SIZE_IN_BITS countLeadingZeros :: Int -> Int countLeadingZeros (I# Int# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# clz# (Int# -> Word# int2Word# Int# x#))) {-# INLINE countLeadingZeros #-} countTrailingZeros :: Int -> Int countTrailingZeros (I# Int# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# ctz# (Int# -> Word# int2Word# Int# x#))) {-# INLINE countTrailingZeros #-}

instance Bits Word where {-# INLINE shift #-} {-# INLINE bit #-} {-# INLINE testBit #-} {-# INLINE popCount #-}

([W#](../https://hackage.haskell.org/package/ghc-prim-0.9.0/docs/src/GHC.Types.html#W%23/GHC.Types.html#W%23) Word#

x#) .&. :: Word -> Word -> Word .&. (W# Word# y#) = Word# -> Word W# (Word# x# Word# -> Word# -> Word# and# Word# y#) (W# Word# x#) .|. :: Word -> Word -> Word .|. (W# Word# y#) = Word# -> Word W# (Word# x# Word# -> Word# -> Word# or# Word# y#) (W# Word# x#) xor :: Word -> Word -> Word xor (W# Word# y#) = Word# -> Word W# (Word# x# Word# -> Word# -> Word# xor# Word# y#) complement :: Word -> Word complement (W# Word# x#) = Word# -> Word W# (Word# -> Word# not# Word# x#) (W# Word# x#) shift :: Word -> Int -> Word shift (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Word# -> Word W# (Word# x# Word# -> Int# -> Word# shiftL# Int# i#) | Bool otherwise = Word# -> Word W# (Word# x# Word# -> Int# -> Word# shiftRL# Int# -> Int# negateInt# Int# i#) (W# Word# x#) shiftL :: Word -> Int -> Word shiftL (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Word# -> Word W# (Word# x# Word# -> Int# -> Word# shiftL# Int# i#) | Bool otherwise = Word forall a. a overflowError (W# Word# x#) unsafeShiftL :: Word -> Int -> Word unsafeShiftL (I# Int# i#) = Word# -> Word W# (Word# x# Word# -> Int# -> Word# uncheckedShiftL# Int# i#) (W# Word# x#) shiftR :: Word -> Int -> Word shiftR (I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Word# -> Word W# (Word# x# Word# -> Int# -> Word# shiftRL# Int# i#) | Bool otherwise = Word forall a. a overflowError (W# Word# x#) unsafeShiftR :: Word -> Int -> Word unsafeShiftR (I# Int# i#) = Word# -> Word W# (Word# x# Word# -> Int# -> Word# uncheckedShiftRL# Int# i#) (W# Word# x#) rotate :: Word -> Int -> Word rotate (I# Int# i#) | Int# -> Bool isTrue# (Int# i'# Int# -> 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# (Int# wsib Int# -> Int# -> Int# -# Int# i'#))) where !i'# :: Int# i'# = Int# i# Int# -> Int# -> Int# andI# (Int# wsib Int# -> Int# -> Int# -# Int# 1#) !wsib :: Int# wsib = WORD_SIZE_IN_BITS#
bitSizeMaybe :: Word -> Maybe Int bitSizeMaybe Word i = Int -> Maybe Int forall a. a -> Maybe a Just (Word -> Int forall b. FiniteBits b => b -> Int finiteBitSize Word i) bitSize :: Word -> Int bitSize Word i = Word -> Int forall b. FiniteBits b => b -> Int finiteBitSize Word i isSigned :: Word -> Bool isSigned Word _ = Bool False popCount :: Word -> Int popCount (W# Word# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# popCnt# Word# x#)) bit :: Int -> Word bit = Int -> Word forall a. (Bits a, Num a) => Int -> a bitDefault testBit :: Word -> Int -> Bool testBit = Word -> Int -> Bool forall a. (Bits a, Num a) => a -> Int -> Bool testBitDefault

instance FiniteBits Word where finiteBitSize :: Word -> Int finiteBitSize Word _ = WORD_SIZE_IN_BITS countLeadingZeros :: Word -> Int countLeadingZeros (W# Word# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# clz# Word# x#)) {-# INLINE countLeadingZeros #-} countTrailingZeros :: Word -> Int countTrailingZeros (W# Word# x#) = Int# -> Int I# (Word# -> Int# word2Int# (Word# -> Word# ctz# Word# x#)) {-# INLINE countTrailingZeros #-}

instance Bits Integer where .&. :: Integer -> Integer -> Integer (.&.) = Integer -> Integer -> Integer integerAnd .|. :: Integer -> Integer -> Integer (.|.) = Integer -> Integer -> Integer integerOr xor :: Integer -> Integer -> Integer xor = Integer -> Integer -> Integer integerXor complement :: Integer -> Integer complement = Integer -> Integer integerComplement unsafeShiftR :: Integer -> Int -> Integer unsafeShiftR Integer x Int i = Integer -> Word -> Integer integerShiftR Integer x (Int -> Word forall a b. (Integral a, Num b) => a -> b fromIntegral Int i) unsafeShiftL :: Integer -> Int -> Integer unsafeShiftL Integer x Int i = Integer -> Word -> Integer integerShiftL Integer x (Int -> Word forall a b. (Integral a, Num b) => a -> b fromIntegral Int i) shiftR :: Integer -> Int -> Integer shiftR Integer x i :: Int i@(I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Integer -> Int -> Integer forall a. Bits a => a -> Int -> a unsafeShiftR Integer x Int i | Bool otherwise = Integer forall a. a overflowError shiftL :: Integer -> Int -> Integer shiftL Integer x i :: Int i@(I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Integer -> Int -> Integer forall a. Bits a => a -> Int -> a unsafeShiftL Integer x Int i | Bool otherwise = Integer forall a. a overflowError shift :: Integer -> Int -> Integer shift Integer x Int i | Int i Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >= Int 0 = Integer -> Word -> Integer integerShiftL Integer x (Int -> Word forall a b. (Integral a, Num b) => a -> b fromIntegral Int i) | Bool otherwise = Integer -> Word -> Integer integerShiftR Integer x (Int -> Word forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> Int forall a. Num a => a -> a negate Int i)) testBit :: Integer -> Int -> Bool testBit Integer x Int i = Integer -> Word -> Bool integerTestBit Integer x (Int -> Word forall a b. (Integral a, Num b) => a -> b fromIntegral Int i) zeroBits :: Integer zeroBits = Integer integerZero

bit :: Int -> Integer bit (I# Int# i) = Word# -> Integer integerBit# (Int# -> Word# int2Word# Int# i) popCount :: Integer -> Int popCount Integer x = Int# -> Int I# (Integer -> Int# integerPopCount# Integer x)

rotate :: Integer -> Int -> Integer rotate Integer x Int i = Integer -> Int -> Integer forall a. Bits a => a -> Int -> a shift Integer x Int i

bitSizeMaybe :: Integer -> Maybe Int bitSizeMaybe Integer _ = Maybe Int forall a. Maybe a Nothing bitSize :: Integer -> Int bitSize Integer _ = [Char] -> Int forall a. [Char] -> a errorWithoutStackTrace [Char] "Data.Bits.bitSize(Integer)" isSigned :: Integer -> Bool isSigned Integer _ = Bool True

instance Bits Natural where .&. :: Natural -> Natural -> Natural (.&.) = Natural -> Natural -> Natural naturalAnd .|. :: Natural -> Natural -> Natural (.|.) = Natural -> Natural -> Natural naturalOr xor :: Natural -> Natural -> Natural xor = Natural -> Natural -> Natural naturalXor complement :: Natural -> Natural complement Natural _ = [Char] -> Natural forall a. [Char] -> a errorWithoutStackTrace [Char] "Bits.complement: Natural complement undefined" unsafeShiftR :: Natural -> Int -> Natural unsafeShiftR Natural x Int i = Natural -> Word -> Natural naturalShiftR Natural x (Int -> Word forall a b. (Integral a, Num b) => a -> b fromIntegral Int i) unsafeShiftL :: Natural -> Int -> Natural unsafeShiftL Natural x Int i = Natural -> Word -> Natural naturalShiftL Natural x (Int -> Word forall a b. (Integral a, Num b) => a -> b fromIntegral Int i) shiftR :: Natural -> Int -> Natural shiftR Natural x i :: Int i@(I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Natural -> Int -> Natural forall a. Bits a => a -> Int -> a unsafeShiftR Natural x Int i | Bool otherwise = Natural forall a. a overflowError shiftL :: Natural -> Int -> Natural shiftL Natural x i :: Int i@(I# Int# i#) | Int# -> Bool isTrue# (Int# i# Int# -> Int# -> Int# >=# Int# 0#) = Natural -> Int -> Natural forall a. Bits a => a -> Int -> a unsafeShiftL Natural x Int i | Bool otherwise = Natural forall a. a overflowError shift :: Natural -> Int -> Natural shift Natural x Int i | Int i Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >= Int 0 = Natural -> Word -> Natural naturalShiftL Natural x (Int -> Word forall a b. (Integral a, Num b) => a -> b fromIntegral Int i) | Bool otherwise = Natural -> Word -> Natural naturalShiftR Natural x (Int -> Word forall a b. (Integral a, Num b) => a -> b fromIntegral (Int -> Int forall a. Num a => a -> a negate Int i)) testBit :: Natural -> Int -> Bool testBit Natural x Int i = Natural -> Word -> Bool naturalTestBit Natural x (Int -> Word forall a b. (Integral a, Num b) => a -> b fromIntegral Int i) zeroBits :: Natural zeroBits = Natural naturalZero setBit :: Natural -> Int -> Natural setBit Natural x Int i = Natural -> Word -> Natural naturalSetBit Natural x (Int -> Word forall a b. (Integral a, Num b) => a -> b fromIntegral Int i) clearBit :: Natural -> Int -> Natural clearBit Natural x Int i = Natural -> Word -> Natural naturalClearBit Natural x (Int -> Word forall a b. (Integral a, Num b) => a -> b fromIntegral Int i) complementBit :: Natural -> Int -> Natural complementBit Natural x Int i = Natural -> Word -> Natural naturalComplementBit Natural x (Int -> Word forall a b. (Integral a, Num b) => a -> b fromIntegral Int i)

bit :: Int -> Natural bit (I# Int# i) = Word# -> Natural naturalBit# (Int# -> Word# int2Word# Int# i) popCount :: Natural -> Int popCount Natural x = Int# -> Int I# (Word# -> Int# word2Int# (Natural -> Word# naturalPopCount# Natural x))

rotate :: Natural -> Int -> Natural rotate Natural x Int i = Natural -> Int -> Natural forall a. Bits a => a -> Int -> a shift Natural x Int i

bitSizeMaybe :: Natural -> Maybe Int bitSizeMaybe Natural _ = Maybe Int forall a. Maybe a Nothing bitSize :: Natural -> Int bitSize Natural _ = [Char] -> Int forall a. [Char] -> a errorWithoutStackTrace [Char] "Data.Bits.bitSize(Natural)" isSigned :: Natural -> Bool isSigned Natural _ = Bool False

toIntegralSized :: (Integral a, Integral b, Bits a, Bits b) => a -> Maybe b toIntegralSized :: forall a b. (Integral a, Integral b, Bits a, Bits b) => a -> Maybe b toIntegralSized a x
| Bool -> (a -> Bool) -> Maybe a -> Bool forall b a. b -> (a -> b) -> Maybe a -> b maybe Bool True (a -> a -> Bool forall a. Ord a => a -> a -> Bool <= a x) Maybe a yMinBound , Bool -> (a -> Bool) -> Maybe a -> Bool forall b a. b -> (a -> b) -> Maybe a -> b maybe Bool True (a x a -> a -> Bool forall a. Ord a => a -> a -> Bool <=) Maybe a yMaxBound = b -> Maybe b forall a. a -> Maybe a Just b y | Bool otherwise = Maybe b forall a. Maybe a Nothing where y :: b y = a -> b forall a b. (Integral a, Num b) => a -> b fromIntegral a x

xWidth :: Maybe Int

xWidth = a -> Maybe Int forall a. Bits a => a -> Maybe Int bitSizeMaybe a x yWidth :: Maybe Int yWidth = b -> Maybe Int forall a. Bits a => a -> Maybe Int bitSizeMaybe b y

yMinBound :: Maybe a

yMinBound | a -> b -> Bool forall a b. (Bits a, Bits b) => a -> b -> Bool isBitSubType a x b y = Maybe a forall a. Maybe a Nothing | a -> Bool forall a. Bits a => a -> Bool isSigned a x, Bool -> Bool not (b -> Bool forall a. Bits a => a -> Bool isSigned b y) = a -> Maybe a forall a. a -> Maybe a Just a 0 | a -> Bool forall a. Bits a => a -> Bool isSigned a x, b -> Bool forall a. Bits a => a -> Bool isSigned b y , Just Int yW <- Maybe Int yWidth = a -> Maybe a forall a. a -> Maybe a Just (a -> a forall a. Num a => a -> a negate (a -> a) -> a -> a forall a b. (a -> b) -> a -> b $ Int -> a forall a. Bits a => Int -> a bit (Int yWInt -> Int -> Int forall a. Num a => a -> a -> a -Int 1)) | Bool otherwise = Maybe a forall a. Maybe a Nothing

yMaxBound :: Maybe a

yMaxBound | a -> b -> Bool forall a b. (Bits a, Bits b) => a -> b -> Bool isBitSubType a x b y = Maybe a forall a. Maybe a Nothing | a -> Bool forall a. Bits a => a -> Bool isSigned a x, Bool -> Bool not (b -> Bool forall a. Bits a => a -> Bool isSigned b y) , Just Int xW <- Maybe Int xWidth, Just Int yW <- Maybe Int yWidth , Int xW Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <= Int yWInt -> Int -> Int forall a. Num a => a -> a -> a +Int 1 = Maybe a forall a. Maybe a Nothing | Just Int yW <- Maybe Int yWidth = if b -> Bool forall a. Bits a => a -> Bool isSigned b y then a -> Maybe a forall a. a -> Maybe a Just (Int -> a forall a. Bits a => Int -> a bit (Int yWInt -> Int -> Int forall a. Num a => a -> a -> a -Int 1)a -> a -> a forall a. Num a => a -> a -> a -a 1) else a -> Maybe a forall a. a -> Maybe a Just (Int -> a forall a. Bits a => Int -> a bit Int yWa -> a -> a forall a. Num a => a -> a -> a -a 1) | Bool otherwise = Maybe a forall a. Maybe a Nothing {-# INLINABLE toIntegralSized #-}

isBitSubType :: (Bits a, Bits b) => a -> b -> Bool isBitSubType :: forall a b. (Bits a, Bits b) => a -> b -> Bool isBitSubType a x b y

| Maybe Int xWidth Maybe Int -> Maybe Int -> Bool forall a. Eq a => a -> a -> Bool == Maybe Int yWidth, Bool xSigned Bool -> Bool -> Bool forall a. Eq a => a -> a -> Bool == Bool ySigned = Bool True

| Bool ySigned, Maybe Int forall a. Maybe a Nothing Maybe Int -> Maybe Int -> Bool forall a. Eq a => a -> a -> Bool == Maybe Int yWidth = Bool True | Bool -> Bool not Bool xSigned, Bool -> Bool not Bool ySigned, Maybe Int forall a. Maybe a Nothing Maybe Int -> Maybe Int -> Bool forall a. Eq a => a -> a -> Bool == Maybe Int yWidth = Bool True

| Bool xSigned Bool -> Bool -> Bool forall a. Eq a => a -> a -> Bool == Bool ySigned, Just Int xW <- Maybe Int xWidth, Just Int yW <- Maybe Int yWidth = Int xW Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <= Int yW | Bool -> Bool not Bool xSigned, Bool ySigned, Just Int xW <- Maybe Int xWidth, Just Int yW <- Maybe Int yWidth = Int xW Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int yW

| Bool otherwise = Bool False where xWidth :: Maybe Int xWidth = a -> Maybe Int forall a. Bits a => a -> Maybe Int bitSizeMaybe a x xSigned :: Bool xSigned = a -> Bool forall a. Bits a => a -> Bool isSigned a x

yWidth :: Maybe Int

yWidth = b -> Maybe Int forall a. Bits a => a -> Maybe Int bitSizeMaybe b y ySigned :: Bool ySigned = b -> Bool forall a. Bits a => a -> Bool isSigned b y {-# INLINE isBitSubType #-}