(original) (raw)
{-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns, MagicHash #-}
module Data.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.Enum import GHC.Num import GHC.Base import GHC.Real
#if defined(MIN_VERSION_integer_gmp) import GHC.Integer.GMP.Internals (bitInteger, popCountInteger) #endif
infixl 8 [shift](Data.Bits.html#shift)
, [rotate](Data.Bits.html#rotate)
, [shiftL](Data.Bits.html#shiftL)
, [shiftR](Data.Bits.html#shiftR)
, [rotateL](Data.Bits.html#rotateL)
, [rotateR](Data.Bits.html#rotateR)
infixl 7 .&.
infixl 6 [xor](Data.Bits.html#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 #-}
([.&.](Data.Bits.html#.%26.)) :: [a](#local-6989586621679049970) -> [a](#local-6989586621679049970) -> [a](#local-6989586621679049970)
([.|.](Data.Bits.html#.%7C.)) :: [a](#local-6989586621679049970) -> [a](#local-6989586621679049970) -> [a](#local-6989586621679049970)
[xor](Data.Bits.html#xor) :: [a](#local-6989586621679049970) -> [a](#local-6989586621679049970) -> [a](#local-6989586621679049970)
[complement](Data.Bits.html#complement) :: [a](#local-6989586621679049970) -> [a](#local-6989586621679049970)
[shift](Data.Bits.html#shift) :: [a](#local-6989586621679049970) -> Int -> [a](#local-6989586621679049970)
[x](#local-6989586621679049971) `[shift](Data.Bits.html#shift)` [i](#local-6989586621679049972) | [i](#local-6989586621679049972)<0 = [x](#local-6989586621679049971) `[shiftR](Data.Bits.html#shiftR)` (-[i](#local-6989586621679049972))
| [i](#local-6989586621679049972)>0 = [x](#local-6989586621679049971) `[shiftL](Data.Bits.html#shiftL)` [i](#local-6989586621679049972)
| [otherwise](GHC.Base.html#otherwise) = [x](#local-6989586621679049971)
[rotate](Data.Bits.html#rotate) :: [a](#local-6989586621679049970) -> Int -> [a](#local-6989586621679049970)
[x](#local-6989586621679049973) `[rotate](Data.Bits.html#rotate)` [i](#local-6989586621679049974) | [i](#local-6989586621679049974)<0 = [x](#local-6989586621679049973) `[rotateR](Data.Bits.html#rotateR)` (-[i](#local-6989586621679049974))
| [i](#local-6989586621679049974)>0 = [x](#local-6989586621679049973) `[rotateL](Data.Bits.html#rotateL)` [i](#local-6989586621679049974)
| [otherwise](GHC.Base.html#otherwise) = [x](#local-6989586621679049973)
[zeroBits](Data.Bits.html#zeroBits) :: [a](#local-6989586621679049970)
[zeroBits](Data.Bits.html#zeroBits) = [clearBit](Data.Bits.html#clearBit) ([bit](Data.Bits.html#bit) 0) 0
[bit](Data.Bits.html#bit) :: Int -> [a](#local-6989586621679049970)
[setBit](Data.Bits.html#setBit) :: [a](#local-6989586621679049970) -> Int -> [a](#local-6989586621679049970)
[clearBit](Data.Bits.html#clearBit) :: [a](#local-6989586621679049970) -> Int -> [a](#local-6989586621679049970)
[complementBit](Data.Bits.html#complementBit) :: [a](#local-6989586621679049970) -> Int -> [a](#local-6989586621679049970)
[testBit](Data.Bits.html#testBit) :: [a](#local-6989586621679049970) -> Int -> Bool
[bitSizeMaybe](Data.Bits.html#bitSizeMaybe) :: [a](#local-6989586621679049970) -> [Maybe](GHC.Maybe.html#Maybe) Int
[bitSize](Data.Bits.html#bitSize) :: [a](#local-6989586621679049970) -> Int
[bitSize](Data.Bits.html#bitSize) [b](#local-6989586621679049975) = [fromMaybe](Data.Maybe.html#fromMaybe) ([error](GHC.Err.html#error) "bitSize is undefined") ([bitSizeMaybe](Data.Bits.html#bitSizeMaybe) [b](#local-6989586621679049975))
[isSigned](Data.Bits.html#isSigned) :: [a](#local-6989586621679049970) -> Bool
{-# INLINE setBit #-}
{-# INLINE clearBit #-}
{-# INLINE complementBit #-}
[x](#local-6989586621679049976) `[setBit](Data.Bits.html#setBit)` [i](#local-6989586621679049977) = [x](#local-6989586621679049976) [.|.](Data.Bits.html#.%7C.) [bit](Data.Bits.html#bit) [i](#local-6989586621679049977)
[x](#local-6989586621679049978) `[clearBit](Data.Bits.html#clearBit)` [i](#local-6989586621679049979) = [x](#local-6989586621679049978) [.&.](Data.Bits.html#.%26.) [complement](Data.Bits.html#complement) ([bit](Data.Bits.html#bit) [i](#local-6989586621679049979))
[x](#local-6989586621679049980) `[complementBit](Data.Bits.html#complementBit)` [i](#local-6989586621679049981) = [x](#local-6989586621679049980) `[xor](Data.Bits.html#xor)` [bit](Data.Bits.html#bit) [i](#local-6989586621679049981)
[shiftL](Data.Bits.html#shiftL) :: [a](#local-6989586621679049970) -> Int -> [a](#local-6989586621679049970)
{-# INLINE shiftL #-}
[x](#local-6989586621679049982) `[shiftL](Data.Bits.html#shiftL)` [i](#local-6989586621679049983) = [x](#local-6989586621679049982) `[shift](Data.Bits.html#shift)` [i](#local-6989586621679049983)
[unsafeShiftL](Data.Bits.html#unsafeShiftL) :: [a](#local-6989586621679049970) -> Int -> [a](#local-6989586621679049970)
{-# INLINE unsafeShiftL #-}
[x](#local-6989586621679049984) `[unsafeShiftL](Data.Bits.html#unsafeShiftL)` [i](#local-6989586621679049985) = [x](#local-6989586621679049984) `[shiftL](Data.Bits.html#shiftL)` [i](#local-6989586621679049985)
[shiftR](Data.Bits.html#shiftR) :: [a](#local-6989586621679049970) -> Int -> [a](#local-6989586621679049970)
{-# INLINE shiftR #-}
[x](#local-6989586621679049986) `[shiftR](Data.Bits.html#shiftR)` [i](#local-6989586621679049987) = [x](#local-6989586621679049986) `[shift](Data.Bits.html#shift)` (-[i](#local-6989586621679049987))
[unsafeShiftR](Data.Bits.html#unsafeShiftR) :: [a](#local-6989586621679049970) -> Int -> [a](#local-6989586621679049970)
{-# INLINE unsafeShiftR #-}
[x](#local-6989586621679049988) `[unsafeShiftR](Data.Bits.html#unsafeShiftR)` [i](#local-6989586621679049989) = [x](#local-6989586621679049988) `[shiftR](Data.Bits.html#shiftR)` [i](#local-6989586621679049989)
[rotateL](Data.Bits.html#rotateL) :: [a](#local-6989586621679049970) -> Int -> [a](#local-6989586621679049970)
{-# INLINE rotateL #-}
[x](#local-6989586621679049990) `[rotateL](Data.Bits.html#rotateL)` [i](#local-6989586621679049991) = [x](#local-6989586621679049990) `[rotate](Data.Bits.html#rotate)` [i](#local-6989586621679049991)
[rotateR](Data.Bits.html#rotateR) :: [a](#local-6989586621679049970) -> Int -> [a](#local-6989586621679049970)
{-# INLINE rotateR #-}
[x](#local-6989586621679049992) `[rotateR](Data.Bits.html#rotateR)` [i](#local-6989586621679049993) = [x](#local-6989586621679049992) `[rotate](Data.Bits.html#rotate)` (-[i](#local-6989586621679049993))
[popCount](Data.Bits.html#popCount) :: [a](#local-6989586621679049970) -> Int
class Bits b => FiniteBits b where
[finiteBitSize](Data.Bits.html#finiteBitSize) :: [b](#local-6989586621679049961) -> Int
[countLeadingZeros](Data.Bits.html#countLeadingZeros) :: [b](#local-6989586621679049961) -> Int
[countLeadingZeros](Data.Bits.html#countLeadingZeros) [x](#local-6989586621679049962) = ([w](#local-6989586621679049964)-1) - [go](#local-6989586621679049963) ([w](#local-6989586621679049964)-1)
where
[go](#local-6989586621679049963) [i](#local-6989586621679049965) | [i](#local-6989586621679049965) < 0 = [i](#local-6989586621679049965)
| [testBit](Data.Bits.html#testBit) [x](#local-6989586621679049962) [i](#local-6989586621679049965) = [i](#local-6989586621679049965)
| [otherwise](GHC.Base.html#otherwise) = [go](#local-6989586621679049963) ([i](#local-6989586621679049965)-1)
[w](#local-6989586621679049964) = [finiteBitSize](Data.Bits.html#finiteBitSize) [x](#local-6989586621679049962)
[countTrailingZeros](Data.Bits.html#countTrailingZeros) :: [b](#local-6989586621679049961) -> Int
[countTrailingZeros](Data.Bits.html#countTrailingZeros) [x](#local-6989586621679049966) = [go](#local-6989586621679049967) 0
where
[go](#local-6989586621679049967) [i](#local-6989586621679049969) | [i](#local-6989586621679049969) >= [w](#local-6989586621679049968) = [i](#local-6989586621679049969)
| [testBit](Data.Bits.html#testBit) [x](#local-6989586621679049966) [i](#local-6989586621679049969) = [i](#local-6989586621679049969)
| [otherwise](GHC.Base.html#otherwise) = [go](#local-6989586621679049967) ([i](#local-6989586621679049969)[+](GHC.Num.html#%2B)1)
[w](#local-6989586621679049968) = [finiteBitSize](Data.Bits.html#finiteBitSize) [x](#local-6989586621679049966)
bitDefault :: (Bits a, Num a) => Int -> a
bitDefault = [i](#local-6989586621679050078) -> 1 [shiftL](Data.Bits.html#shiftL)
i
{-# INLINE bitDefault #-}
testBitDefault :: (Bits a, Num a) => a -> Int -> Bool testBitDefault = [x](#local-6989586621679050079) i -> (x .&. bit i) /= 0 {-# INLINE testBitDefault #-}
popCountDefault :: (Bits a, Num a) => a -> Int popCountDefault = go 0 where go 0 = c go c w = go (c+1) (w .&. (w - 1)) {-# INLINABLE popCountDefault #-}
instance Bits Bool where (.&.) = (&&)
([.|.](Data.Bits.html#.%7C.)) = (||)
[xor](Data.Bits.html#xor) = (/=)
[complement](Data.Bits.html#complement) = not
[shift](Data.Bits.html#shift) [x](#local-6989586621679050068) 0 = [x](#local-6989586621679050068)
shift _ _ = False
[rotate](Data.Bits.html#rotate) [x](#local-6989586621679050069) _ = [x](#local-6989586621679050069)
[bit](Data.Bits.html#bit) 0 = True
bit _ = False
[testBit](Data.Bits.html#testBit) [x](#local-6989586621679050070) 0 = [x](#local-6989586621679050070)
testBit _ _ = False
[bitSizeMaybe](Data.Bits.html#bitSizeMaybe) _ = [Just](GHC.Maybe.html#Just) 1
[bitSize](Data.Bits.html#bitSize) _ = 1
[isSigned](Data.Bits.html#isSigned) _ = False
[popCount](Data.Bits.html#popCount) False = 0
popCount True = 1
instance FiniteBits Bool where finiteBitSize _ = 1 countTrailingZeros x = if x then 0 else 1 countLeadingZeros x = if x then 0 else 1
instance Bits Int where {-# INLINE shift #-} {-# INLINE bit #-} {-# INLINE testBit #-}
[zeroBits](Data.Bits.html#zeroBits) = 0
[bit](Data.Bits.html#bit) = [bitDefault](Data.Bits.html#bitDefault)
[testBit](Data.Bits.html#testBit) = [testBitDefault](Data.Bits.html#testBitDefault)
(I# [x#](#local-6989586621679050042)) [.&.](Data.Bits.html#.%26.) (I# [y#](#local-6989586621679050043)) = I# ([x#](#local-6989586621679050042) `andI#` [y#](#local-6989586621679050043))
(I# [x#](#local-6989586621679050044)) [.|.](Data.Bits.html#.%7C.) (I# [y#](#local-6989586621679050045)) = I# ([x#](#local-6989586621679050044) `orI#` [y#](#local-6989586621679050045))
(I# [x#](#local-6989586621679050046)) `[xor](Data.Bits.html#xor)` (I# [y#](#local-6989586621679050047)) = I# ([x#](#local-6989586621679050046) `xorI#` [y#](#local-6989586621679050047))
[complement](Data.Bits.html#complement) (I# [x#](#local-6989586621679050048)) = I# (notI# [x#](#local-6989586621679050048))
(I# [x#](#local-6989586621679050049)) `[shift](Data.Bits.html#shift)` (I# [i#](#local-6989586621679050050))
| isTrue# ([i#](#local-6989586621679050050) >=# 0#) = I# ([x#](#local-6989586621679050049) `[iShiftL#](GHC.Base.html#iShiftL%23)` [i#](#local-6989586621679050050))
| [otherwise](GHC.Base.html#otherwise) = I# ([x#](#local-6989586621679050049) `[iShiftRA#](GHC.Base.html#iShiftRA%23)` negateInt# [i#](#local-6989586621679050050))
(I# [x#](#local-6989586621679050051)) `[shiftL](Data.Bits.html#shiftL)` (I# [i#](#local-6989586621679050052)) = I# ([x#](#local-6989586621679050051) `[iShiftL#](GHC.Base.html#iShiftL%23)` [i#](#local-6989586621679050052))
(I# [x#](#local-6989586621679050053)) `[unsafeShiftL](Data.Bits.html#unsafeShiftL)` (I# [i#](#local-6989586621679050054)) = I# ([x#](#local-6989586621679050053) `uncheckedIShiftL#` [i#](#local-6989586621679050054))
(I# [x#](#local-6989586621679050055)) `[shiftR](Data.Bits.html#shiftR)` (I# [i#](#local-6989586621679050056)) = I# ([x#](#local-6989586621679050055) `[iShiftRA#](GHC.Base.html#iShiftRA%23)` [i#](#local-6989586621679050056))
(I# [x#](#local-6989586621679050057)) `[unsafeShiftR](Data.Bits.html#unsafeShiftR)` (I# [i#](#local-6989586621679050058)) = I# ([x#](#local-6989586621679050057) `uncheckedIShiftRA#` [i#](#local-6989586621679050058))
{-# INLINE rotate #-}
(I# [x#](#local-6989586621679050059)) `[rotate](Data.Bits.html#rotate)` (I# [i#](#local-6989586621679050060)) =
I# (([x#](#local-6989586621679050059) `uncheckedIShiftL#` [i'#](#local-6989586621679050061)) `orI#` ([x#](#local-6989586621679050059) `uncheckedIShiftRL#` ([wsib](#local-6989586621679050062) -# [i'#](#local-6989586621679050061))))
where
![i'#](#local-6989586621679050061) = [i#](#local-6989586621679050060) `andI#` ([wsib](#local-6989586621679050062) -# 1#)
![wsib](#local-6989586621679050062) = WORD_SIZE_IN_BITS#
[bitSizeMaybe](Data.Bits.html#bitSizeMaybe) [i](#local-6989586621679050063) = [Just](GHC.Maybe.html#Just) ([finiteBitSize](Data.Bits.html#finiteBitSize) [i](#local-6989586621679050063))
[bitSize](Data.Bits.html#bitSize) [i](#local-6989586621679050064) = [finiteBitSize](Data.Bits.html#finiteBitSize) [i](#local-6989586621679050064)
[popCount](Data.Bits.html#popCount) (I# [x#](#local-6989586621679050065)) = I# (word2Int# (popCnt# (int2Word# [x#](#local-6989586621679050065))))
[isSigned](Data.Bits.html#isSigned) _ = True
instance FiniteBits Int where finiteBitSize _ = WORD_SIZE_IN_BITS countLeadingZeros (I# x#) = I# (word2Int# (clz# (int2Word# x#))) countTrailingZeros (I# x#) = I# (word2Int# (ctz# (int2Word# x#)))
instance Bits Word where {-# INLINE shift #-} {-# INLINE bit #-} {-# INLINE testBit #-}
(W# [x#](#local-6989586621679050015)) [.&.](Data.Bits.html#.%26.) (W# [y#](#local-6989586621679050016)) = W# ([x#](#local-6989586621679050015) `and#` [y#](#local-6989586621679050016))
(W# [x#](#local-6989586621679050017)) [.|.](Data.Bits.html#.%7C.) (W# [y#](#local-6989586621679050018)) = W# ([x#](#local-6989586621679050017) `or#` [y#](#local-6989586621679050018))
(W# [x#](#local-6989586621679050019)) `[xor](Data.Bits.html#xor)` (W# [y#](#local-6989586621679050020)) = W# ([x#](#local-6989586621679050019) `xor#` [y#](#local-6989586621679050020))
[complement](Data.Bits.html#complement) (W# [x#](#local-6989586621679050021)) = W# ([x#](#local-6989586621679050021) `xor#` [mb#](#local-6989586621679050022))
where !(W# [mb#](#local-6989586621679050022)) = [maxBound](GHC.Enum.html#maxBound)
(W# [x#](#local-6989586621679050023)) `[shift](Data.Bits.html#shift)` (I# [i#](#local-6989586621679050024))
| isTrue# ([i#](#local-6989586621679050024) >=# 0#) = W# ([x#](#local-6989586621679050023) `[shiftL#](GHC.Base.html#shiftL%23)` [i#](#local-6989586621679050024))
| [otherwise](GHC.Base.html#otherwise) = W# ([x#](#local-6989586621679050023) `[shiftRL#](GHC.Base.html#shiftRL%23)` negateInt# [i#](#local-6989586621679050024))
(W# [x#](#local-6989586621679050025)) `[shiftL](Data.Bits.html#shiftL)` (I# [i#](#local-6989586621679050026)) = W# ([x#](#local-6989586621679050025) `[shiftL#](GHC.Base.html#shiftL%23)` [i#](#local-6989586621679050026))
(W# [x#](#local-6989586621679050027)) `[unsafeShiftL](Data.Bits.html#unsafeShiftL)` (I# [i#](#local-6989586621679050028)) = W# ([x#](#local-6989586621679050027) `uncheckedShiftL#` [i#](#local-6989586621679050028))
(W# [x#](#local-6989586621679050029)) `[shiftR](Data.Bits.html#shiftR)` (I# [i#](#local-6989586621679050030)) = W# ([x#](#local-6989586621679050029) `[shiftRL#](GHC.Base.html#shiftRL%23)` [i#](#local-6989586621679050030))
(W# [x#](#local-6989586621679050031)) `[unsafeShiftR](Data.Bits.html#unsafeShiftR)` (I# [i#](#local-6989586621679050032)) = W# ([x#](#local-6989586621679050031) `uncheckedShiftRL#` [i#](#local-6989586621679050032))
(W# [x#](#local-6989586621679050033)) `[rotate](Data.Bits.html#rotate)` (I# [i#](#local-6989586621679050034))
| isTrue# ([i'#](#local-6989586621679050035) ==# 0#) = W# [x#](#local-6989586621679050033)
| [otherwise](GHC.Base.html#otherwise) = W# (([x#](#local-6989586621679050033) `uncheckedShiftL#` [i'#](#local-6989586621679050035)) `or#` ([x#](#local-6989586621679050033) `uncheckedShiftRL#` ([wsib](#local-6989586621679050036) -# [i'#](#local-6989586621679050035))))
where
![i'#](#local-6989586621679050035) = [i#](#local-6989586621679050034) `andI#` ([wsib](#local-6989586621679050036) -# 1#)
![wsib](#local-6989586621679050036) = WORD_SIZE_IN_BITS#
[bitSizeMaybe](Data.Bits.html#bitSizeMaybe) [i](#local-6989586621679050037) = [Just](GHC.Maybe.html#Just) ([finiteBitSize](Data.Bits.html#finiteBitSize) [i](#local-6989586621679050037))
[bitSize](Data.Bits.html#bitSize) [i](#local-6989586621679050038) = [finiteBitSize](Data.Bits.html#finiteBitSize) [i](#local-6989586621679050038)
[isSigned](Data.Bits.html#isSigned) _ = False
[popCount](Data.Bits.html#popCount) (W# [x#](#local-6989586621679050039)) = I# (word2Int# (popCnt# [x#](#local-6989586621679050039)))
[bit](Data.Bits.html#bit) = [bitDefault](Data.Bits.html#bitDefault)
[testBit](Data.Bits.html#testBit) = [testBitDefault](Data.Bits.html#testBitDefault)
instance FiniteBits Word where finiteBitSize _ = WORD_SIZE_IN_BITS countLeadingZeros (W# x#) = I# (word2Int# (clz# x#)) countTrailingZeros (W# x#) = I# (word2Int# (ctz# x#))
instance Bits Integer where (.&.) = andInteger (.|.) = orInteger xor = xorInteger complement = complementInteger shift x i@(I# i#) | i >= 0 = shiftLInteger x i# | otherwise = shiftRInteger x (negateInt# i#) testBit x (I# i) = testBitInteger x i zeroBits = 0
#if defined(MIN_VERSION_integer_gmp) bit (I# i#) = bitInteger i# popCount x = I# (popCountInteger x) #else bit = bitDefault popCount = popCountDefault #endif
bitSizeMaybe _ = Nothing bitSize _ = errorWithoutStackTrace "Data.Bits.bitSize(Integer)" isSigned _ = True
#if defined(MIN_VERSION_integer_gmp)
instance Bits Natural where
(.&.) = andNatural
(.|.) = orNatural
xor = xorNatural
complement _ = errorWithoutStackTrace
"Bits.complement: Natural complement undefined"
shift x i
| i >= 0 = shiftLNatural x i
| otherwise = shiftRNatural x (negate i)
testBit x i = testBitNatural x i
zeroBits = wordToNaturalBase 0##
clearBit x i = x [xor](Data.Bits.html#xor)
(bit i .&. x)
bit (I# i#) = bitNatural i# popCount x = popCountNatural x
bitSizeMaybe _ = Nothing bitSize _ = errorWithoutStackTrace "Data.Bits.bitSize(Natural)" isSigned _ = False #else
instance Bits Natural where Natural n .&. Natural m = Natural (n .&. m) {-# INLINE (.&.) #-} Natural n .|. Natural m = Natural (n .|. m) {-# INLINE (.|.) #-} xor (Natural n) (Natural m) = Natural (xor n m) {-# INLINE xor #-} complement _ = errorWithoutStackTrace "Bits.complement: Natural complement undefined" {-# INLINE complement #-} shift (Natural n) = Natural . shift n {-# INLINE shift #-} rotate (Natural n) = Natural . rotate n {-# INLINE rotate #-} bit = Natural . bit {-# INLINE bit #-} setBit (Natural n) = Natural . setBit n {-# INLINE setBit #-} clearBit (Natural n) = Natural . clearBit n {-# INLINE clearBit #-} complementBit (Natural n) = Natural . complementBit n {-# INLINE complementBit #-} testBit (Natural n) = testBit n {-# INLINE testBit #-} bitSizeMaybe _ = Nothing {-# INLINE bitSizeMaybe #-} bitSize = errorWithoutStackTrace "Natural: bitSize" {-# INLINE bitSize #-} isSigned _ = False {-# INLINE isSigned #-} shiftL (Natural n) = Natural . shiftL n {-# INLINE shiftL #-} shiftR (Natural n) = Natural . shiftR n {-# INLINE shiftR #-} rotateL (Natural n) = Natural . rotateL n {-# INLINE rotateL #-} rotateR (Natural n) = Natural . rotateR n {-# INLINE rotateR #-} popCount (Natural n) = popCount n {-# INLINE popCount #-} zeroBits = Natural 0
#endif
toIntegralSized :: (Integral a, Integral b, Bits a, Bits b) => a -> Maybe b
toIntegralSized x
| maybe True (<= x) yMinBound
, maybe True (x <=) yMaxBound = Just y
| otherwise = Nothing
where
y = fromIntegral x
[xWidth](#local-6989586621679050087) = [bitSizeMaybe](Data.Bits.html#bitSizeMaybe) [x](#local-6989586621679050085)
[yWidth](#local-6989586621679050088) = [bitSizeMaybe](Data.Bits.html#bitSizeMaybe) [y](#local-6989586621679050086)
[yMinBound](#local-6989586621679050089)
| [isBitSubType](Data.Bits.html#isBitSubType) [x](#local-6989586621679050085) [y](#local-6989586621679050086) = [Nothing](GHC.Maybe.html#Nothing)
| [isSigned](Data.Bits.html#isSigned) [x](#local-6989586621679050085), not ([isSigned](Data.Bits.html#isSigned) [y](#local-6989586621679050086)) = [Just](GHC.Maybe.html#Just) 0
| [isSigned](Data.Bits.html#isSigned) [x](#local-6989586621679050085), [isSigned](Data.Bits.html#isSigned) [y](#local-6989586621679050086)
, [Just](GHC.Maybe.html#Just) [yW](#local-6989586621679050091) <- [yWidth](#local-6989586621679050088) = [Just](GHC.Maybe.html#Just) ([negate](GHC.Num.html#negate) [$](GHC.Base.html#%24) [bit](Data.Bits.html#bit) ([yW](#local-6989586621679050091)-1))
| [otherwise](GHC.Base.html#otherwise) = [Nothing](GHC.Maybe.html#Nothing)
[yMaxBound](#local-6989586621679050090)
| [isBitSubType](Data.Bits.html#isBitSubType) [x](#local-6989586621679050085) [y](#local-6989586621679050086) = [Nothing](GHC.Maybe.html#Nothing)
| [isSigned](Data.Bits.html#isSigned) [x](#local-6989586621679050085), not ([isSigned](Data.Bits.html#isSigned) [y](#local-6989586621679050086))
, [Just](GHC.Maybe.html#Just) [xW](#local-6989586621679050092) <- [xWidth](#local-6989586621679050087), [Just](GHC.Maybe.html#Just) [yW](#local-6989586621679050093) <- [yWidth](#local-6989586621679050088)
, [xW](#local-6989586621679050092) <= [yW](#local-6989586621679050093)[+](GHC.Num.html#%2B)1 = [Nothing](GHC.Maybe.html#Nothing)
| [Just](GHC.Maybe.html#Just) [yW](#local-6989586621679050094) <- [yWidth](#local-6989586621679050088) = if [isSigned](Data.Bits.html#isSigned) [y](#local-6989586621679050086)
then [Just](GHC.Maybe.html#Just) ([bit](Data.Bits.html#bit) ([yW](#local-6989586621679050094)-1)-1)
else [Just](GHC.Maybe.html#Just) ([bit](Data.Bits.html#bit) [yW](#local-6989586621679050094)-1)
| [otherwise](GHC.Base.html#otherwise) = [Nothing](GHC.Maybe.html#Nothing)
{-# INLINABLE toIntegralSized #-}
isBitSubType :: (Bits a, Bits b) => a -> b -> Bool isBitSubType x y
| xWidth == yWidth, xSigned == ySigned = True
| ySigned, Nothing == yWidth = True | not xSigned, not ySigned, Nothing == yWidth = True
| xSigned == ySigned, Just xW <- xWidth, Just yW <- yWidth = xW <= yW | not xSigned, ySigned, Just xW <- xWidth, Just yW <- yWidth = xW < yW
| otherwise = False where xWidth = bitSizeMaybe x xSigned = isSigned x
[yWidth](#local-6989586621679050099) = [bitSizeMaybe](Data.Bits.html#bitSizeMaybe) [y](#local-6989586621679050096)
[ySigned](#local-6989586621679050100) = [isSigned](Data.Bits.html#isSigned) [y](#local-6989586621679050096)
{-# INLINE isBitSubType #-}