{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ScopedTypeVariables #-} module Data.SizedWord ( SizedWord ) where import Data.Bits (Bits, shiftL, shiftR, rotateL, rotateR, bit, testBit, popCount, complement, xor, bitSize, isSigned, (.&.), (.|.), ) import qualified Type.Data.Num as Num import Type.Base.Proxy (Proxy(Proxy)) newtype SizedWord nT = SizedWord Integer sizeT :: SizedWord nT -> Proxy nT sizeT :: SizedWord nT -> Proxy nT sizeT SizedWord nT _ = Proxy nT forall a. Proxy a Proxy mask :: forall nT . Num.Natural nT => Proxy nT -> Integer mask :: Proxy nT -> Integer mask Proxy nT n = Int -> Integer forall a. Bits a => Int -> a bit (Proxy nT -> Int forall x y. (Integer x, Num y) => Proxy x -> y Num.fromInteger Proxy nT n) Integer -> Integer -> Integer forall a. Num a => a -> a -> a - Integer 1 instance Num.Natural nT => Eq (SizedWord nT) where (SizedWord Integer x) == :: SizedWord nT -> SizedWord nT -> Bool == (SizedWord Integer y) = Integer x Integer -> Integer -> Bool forall a. Eq a => a -> a -> Bool == Integer y (SizedWord Integer x) /= :: SizedWord nT -> SizedWord nT -> Bool /= (SizedWord Integer y) = Integer x Integer -> Integer -> Bool forall a. Eq a => a -> a -> Bool /= Integer y instance Num.Natural nT => Show (SizedWord nT) where showsPrec :: Int -> SizedWord nT -> ShowS showsPrec Int prec SizedWord nT n = Int -> Integer -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int prec (Integer -> ShowS) -> Integer -> ShowS forall a b. (a -> b) -> a -> b $ SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT n instance Num.Natural nT => Read (SizedWord nT) where readsPrec :: Int -> ReadS (SizedWord nT) readsPrec Int prec String str0 = [ (Integer -> SizedWord nT forall a. Num a => Integer -> a fromInteger Integer n, String str) | (Integer n, String str) <- Int -> ReadS Integer forall a. Read a => Int -> ReadS a readsPrec Int prec String str0 ] instance Num.Natural nT => Ord (SizedWord nT) where SizedWord nT a compare :: SizedWord nT -> SizedWord nT -> Ordering `compare` SizedWord nT b = SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT a Integer -> Integer -> Ordering forall a. Ord a => a -> a -> Ordering `compare` SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT b instance Num.Natural nT => Bounded (SizedWord nT) where minBound :: SizedWord nT minBound = SizedWord nT 0 maxBound :: SizedWord nT maxBound = Integer -> SizedWord nT forall nT. Integer -> SizedWord nT SizedWord (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ (Integer 1 Integer -> Int -> Integer forall a. Bits a => a -> Int -> a `shiftL` (Proxy nT -> Int forall x y. (Integer x, Num y) => Proxy x -> y Num.fromInteger (Proxy nT forall a. Proxy a Proxy :: Proxy nT))) Integer -> Integer -> Integer forall a. Num a => a -> a -> a - Integer 1 instance Num.Natural nT => Enum (SizedWord nT) where succ :: SizedWord nT -> SizedWord nT succ SizedWord nT x | SizedWord nT x SizedWord nT -> SizedWord nT -> Bool forall a. Eq a => a -> a -> Bool == SizedWord nT forall a. Bounded a => a maxBound = String -> SizedWord nT forall a. HasCallStack => String -> a error (String -> SizedWord nT) -> String -> SizedWord nT forall a b. (a -> b) -> a -> b $ String "Enum.succ{" String -> ShowS forall a. [a] -> [a] -> [a] ++ SizedWord nT -> String forall nT. Natural nT => SizedWord nT -> String showSizedWordType SizedWord nT x String -> ShowS forall a. [a] -> [a] -> [a] ++ String "}: tried to take `succ' of maxBound" | Bool otherwise = SizedWord nT x SizedWord nT -> SizedWord nT -> SizedWord nT forall a. Num a => a -> a -> a + SizedWord nT 1 pred :: SizedWord nT -> SizedWord nT pred SizedWord nT x | SizedWord nT x SizedWord nT -> SizedWord nT -> Bool forall a. Eq a => a -> a -> Bool == SizedWord nT forall a. Bounded a => a minBound = String -> SizedWord nT forall a. HasCallStack => String -> a error (String -> SizedWord nT) -> String -> SizedWord nT forall a b. (a -> b) -> a -> b $ String "Enum.succ{" String -> ShowS forall a. [a] -> [a] -> [a] ++ SizedWord nT -> String forall nT. Natural nT => SizedWord nT -> String showSizedWordType SizedWord nT x String -> ShowS forall a. [a] -> [a] -> [a] ++ String "}: tried to take `pred' of minBound" | Bool otherwise = SizedWord nT x SizedWord nT -> SizedWord nT -> SizedWord nT forall a. Num a => a -> a -> a - SizedWord nT 1 fromEnum :: SizedWord nT -> Int fromEnum s :: SizedWord nT s@(SizedWord Integer x) | Integer x Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool > Int -> Integer forall a. Integral a => a -> Integer toInteger (Int forall a. Bounded a => a maxBound :: Int) = String -> Int forall a. HasCallStack => String -> a error (String -> Int) -> String -> Int forall a b. (a -> b) -> a -> b $ String "Enum.fromEnum{" String -> ShowS forall a. [a] -> [a] -> [a] ++ SizedWord nT -> String forall nT. Natural nT => SizedWord nT -> String showSizedWordType SizedWord nT s String -> ShowS forall a. [a] -> [a] -> [a] ++ String "}: tried to take `fromEnum' on SizedWord greater than maxBound :: Int" | Integer x Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool < Int -> Integer forall a. Integral a => a -> Integer toInteger (Int forall a. Bounded a => a minBound :: Int) = String -> Int forall a. HasCallStack => String -> a error (String -> Int) -> String -> Int forall a b. (a -> b) -> a -> b $ String "Enum.fromEnum{" String -> ShowS forall a. [a] -> [a] -> [a] ++ SizedWord nT -> String forall nT. Natural nT => SizedWord nT -> String showSizedWordType SizedWord nT s String -> ShowS forall a. [a] -> [a] -> [a] ++ String "}: tried to take `fromEnum' on SizedWord smaller than minBound :: Int" | Bool otherwise = Integer -> Int forall a. Num a => Integer -> a fromInteger Integer x toEnum :: Int -> SizedWord nT toEnum Int x | Int x Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > SizedWord nT -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral (SizedWord nT forall a. Bounded a => a maxBound :: SizedWord nT) = String -> SizedWord nT forall a. HasCallStack => String -> a error (String -> SizedWord nT) -> String -> SizedWord nT forall a b. (a -> b) -> a -> b $ String "Enum.fromEnum{" String -> ShowS forall a. [a] -> [a] -> [a] ++ Proxy nT -> String forall nT. Natural nT => Proxy nT -> String showSizedWordTypeProxy Proxy nT n String -> ShowS forall a. [a] -> [a] -> [a] ++ String "}: tried to take `fromEnum' on SizedWord greater than maxBound :: " String -> ShowS forall a. [a] -> [a] -> [a] ++ Proxy nT -> String forall nT. Natural nT => Proxy nT -> String showSizedWordTypeProxy Proxy nT n | Int x Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < SizedWord nT -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral (SizedWord nT forall a. Bounded a => a minBound :: SizedWord nT) = String -> SizedWord nT forall a. HasCallStack => String -> a error (String -> SizedWord nT) -> String -> SizedWord nT forall a b. (a -> b) -> a -> b $ String "Enum.fromEnum{" String -> ShowS forall a. [a] -> [a] -> [a] ++ Proxy nT -> String forall nT. Natural nT => Proxy nT -> String showSizedWordTypeProxy Proxy nT n String -> ShowS forall a. [a] -> [a] -> [a] ++ String "}: tried to take `fromEnum' on SizedWord smaller than minBound :: " String -> ShowS forall a. [a] -> [a] -> [a] ++ Proxy nT -> String forall nT. Natural nT => Proxy nT -> String showSizedWordTypeProxy Proxy nT n | Bool otherwise = Integer -> SizedWord nT forall a. Num a => Integer -> a fromInteger (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ Int -> Integer forall a. Integral a => a -> Integer toInteger Int x where n :: Proxy nT n = Proxy nT forall a. Proxy a Proxy :: Proxy nT instance Num.Natural nT => Num (SizedWord nT) where (SizedWord Integer a) + :: SizedWord nT -> SizedWord nT -> SizedWord nT + (SizedWord Integer b) = Integer -> SizedWord nT forall a. Num a => Integer -> a fromInteger (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ Integer a Integer -> Integer -> Integer forall a. Num a => a -> a -> a + Integer b (SizedWord Integer a) * :: SizedWord nT -> SizedWord nT -> SizedWord nT * (SizedWord Integer b) = Integer -> SizedWord nT forall a. Num a => Integer -> a fromInteger (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ Integer a Integer -> Integer -> Integer forall a. Num a => a -> a -> a * Integer b negate :: SizedWord nT -> SizedWord nT negate s :: SizedWord nT s@(SizedWord Integer n) = Integer -> SizedWord nT forall a. Num a => Integer -> a fromInteger (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ (Integer n Integer -> Integer -> Integer forall a. Bits a => a -> a -> a `xor` Proxy nT -> Integer forall nT. Natural nT => Proxy nT -> Integer mask (SizedWord nT -> Proxy nT forall nT. SizedWord nT -> Proxy nT sizeT SizedWord nT s)) Integer -> Integer -> Integer forall a. Num a => a -> a -> a + Integer 1 SizedWord nT a - :: SizedWord nT -> SizedWord nT -> SizedWord nT - SizedWord nT b = SizedWord nT a SizedWord nT -> SizedWord nT -> SizedWord nT forall a. Num a => a -> a -> a + (SizedWord nT -> SizedWord nT forall a. Num a => a -> a negate SizedWord nT b) fromInteger :: Integer -> SizedWord nT fromInteger Integer n = let fromCardinal :: Integer -> SizedWord nT fromCardinal Integer m = Integer -> SizedWord nT forall nT. Integer -> SizedWord nT SizedWord (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ Integer m Integer -> Integer -> Integer forall a. Bits a => a -> a -> a .&. Proxy nT -> Integer forall nT. Natural nT => Proxy nT -> Integer mask (Proxy nT forall a. Proxy a Proxy :: Proxy nT) in if Integer nInteger -> Integer -> Bool forall a. Ord a => a -> a -> Bool >=Integer 0 then Integer -> SizedWord nT fromCardinal Integer n else SizedWord nT -> SizedWord nT forall a. Num a => a -> a negate (SizedWord nT -> SizedWord nT) -> SizedWord nT -> SizedWord nT forall a b. (a -> b) -> a -> b $ Integer -> SizedWord nT fromCardinal (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ Integer -> Integer forall a. Num a => a -> a negate Integer n abs :: SizedWord nT -> SizedWord nT abs SizedWord nT s = SizedWord nT s signum :: SizedWord nT -> SizedWord nT signum SizedWord nT s | SizedWord nT s SizedWord nT -> SizedWord nT -> Bool forall a. Eq a => a -> a -> Bool == SizedWord nT 0 = SizedWord nT 0 | Bool otherwise = SizedWord nT 1 instance Num.Natural nT => Real (SizedWord nT) where toRational :: SizedWord nT -> Rational toRational SizedWord nT n = Integer -> Rational forall a. Real a => a -> Rational toRational (Integer -> Rational) -> Integer -> Rational forall a b. (a -> b) -> a -> b $ SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT n instance Num.Natural nT => Integral (SizedWord nT) where SizedWord nT a quot :: SizedWord nT -> SizedWord nT -> SizedWord nT `quot` SizedWord nT b = Integer -> SizedWord nT forall a. Num a => Integer -> a fromInteger (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT a Integer -> Integer -> Integer forall a. Integral a => a -> a -> a `quot` SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT b SizedWord nT a rem :: SizedWord nT -> SizedWord nT -> SizedWord nT `rem` SizedWord nT b = Integer -> SizedWord nT forall a. Num a => Integer -> a fromInteger (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT a Integer -> Integer -> Integer forall a. Integral a => a -> a -> a `rem` SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT b SizedWord nT a div :: SizedWord nT -> SizedWord nT -> SizedWord nT `div` SizedWord nT b = Integer -> SizedWord nT forall a. Num a => Integer -> a fromInteger (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT a Integer -> Integer -> Integer forall a. Integral a => a -> a -> a `div` SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT b SizedWord nT a mod :: SizedWord nT -> SizedWord nT -> SizedWord nT `mod` SizedWord nT b = Integer -> SizedWord nT forall a. Num a => Integer -> a fromInteger (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT a Integer -> Integer -> Integer forall a. Integral a => a -> a -> a `mod` SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT b SizedWord nT a quotRem :: SizedWord nT -> SizedWord nT -> (SizedWord nT, SizedWord nT) `quotRem` SizedWord nT b = let (Integer quot_, Integer rem_) = SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT a Integer -> Integer -> (Integer, Integer) forall a. Integral a => a -> a -> (a, a) `quotRem` SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT b in (Integer -> SizedWord nT forall a. Num a => Integer -> a fromInteger Integer quot_, Integer -> SizedWord nT forall a. Num a => Integer -> a fromInteger Integer rem_) SizedWord nT a divMod :: SizedWord nT -> SizedWord nT -> (SizedWord nT, SizedWord nT) `divMod` SizedWord nT b = let (Integer div_, Integer mod_) = SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT a Integer -> Integer -> (Integer, Integer) forall a. Integral a => a -> a -> (a, a) `divMod` SizedWord nT -> Integer forall a. Integral a => a -> Integer toInteger SizedWord nT b in (Integer -> SizedWord nT forall a. Num a => Integer -> a fromInteger Integer div_, Integer -> SizedWord nT forall a. Num a => Integer -> a fromInteger Integer mod_) toInteger :: SizedWord nT -> Integer toInteger (SizedWord Integer x) = Integer x instance Num.Natural nT => Bits (SizedWord nT) where (SizedWord Integer a) .&. :: SizedWord nT -> SizedWord nT -> SizedWord nT .&. (SizedWord Integer b) = Integer -> SizedWord nT forall nT. Integer -> SizedWord nT SizedWord (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ Integer a Integer -> Integer -> Integer forall a. Bits a => a -> a -> a .&. Integer b (SizedWord Integer a) .|. :: SizedWord nT -> SizedWord nT -> SizedWord nT .|. (SizedWord Integer b) = Integer -> SizedWord nT forall nT. Integer -> SizedWord nT SizedWord (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ Integer a Integer -> Integer -> Integer forall a. Bits a => a -> a -> a .|. Integer b (SizedWord Integer a) xor :: SizedWord nT -> SizedWord nT -> SizedWord nT `xor` SizedWord Integer b = Integer -> SizedWord nT forall nT. Integer -> SizedWord nT SizedWord (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ Integer a Integer -> Integer -> Integer forall a. Bits a => a -> a -> a `xor` Integer b complement :: SizedWord nT -> SizedWord nT complement (SizedWord Integer x) = Integer -> SizedWord nT forall nT. Integer -> SizedWord nT SizedWord (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ Integer x Integer -> Integer -> Integer forall a. Bits a => a -> a -> a `xor` Proxy nT -> Integer forall nT. Natural nT => Proxy nT -> Integer mask (Proxy nT forall a. Proxy a Proxy :: Proxy nT) bit :: Int -> SizedWord nT bit Int b = case Integer -> SizedWord nT forall nT. Integer -> SizedWord nT SizedWord (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ Int -> Integer forall a. Bits a => Int -> a bit Int b of SizedWord nT s | Int b Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int 0 -> String -> SizedWord nT forall a. HasCallStack => String -> a error (String -> SizedWord nT) -> String -> SizedWord nT forall a b. (a -> b) -> a -> b $ String "Bits.bit{" String -> ShowS forall a. [a] -> [a] -> [a] ++ SizedWord nT -> String forall nT. Natural nT => SizedWord nT -> String showSizedWordType SizedWord nT s String -> ShowS forall a. [a] -> [a] -> [a] ++ String "}: tried to set negative position" | Int b Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >= SizedWord nT -> Int forall a. Bits a => a -> Int bitSize SizedWord nT s -> String -> SizedWord nT forall a. HasCallStack => String -> a error (String -> SizedWord nT) -> String -> SizedWord nT forall a b. (a -> b) -> a -> b $ String "Bits.bit{" String -> ShowS forall a. [a] -> [a] -> [a] ++ SizedWord nT -> String forall nT. Natural nT => SizedWord nT -> String showSizedWordType SizedWord nT s String -> ShowS forall a. [a] -> [a] -> [a] ++ String "}: tried to set too large position" | Bool otherwise -> SizedWord nT s s :: SizedWord nT s@(SizedWord Integer x) testBit :: SizedWord nT -> Int -> Bool `testBit` Int b | Int b Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int 0 = String -> Bool forall a. HasCallStack => String -> a error (String -> Bool) -> String -> Bool forall a b. (a -> b) -> a -> b $ String "Bits.testBit{" String -> ShowS forall a. [a] -> [a] -> [a] ++ SizedWord nT -> String forall nT. Natural nT => SizedWord nT -> String showSizedWordType SizedWord nT s String -> ShowS forall a. [a] -> [a] -> [a] ++ String "}: tried to test negative position" | Int b Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >= SizedWord nT -> Int forall a. Bits a => a -> Int bitSize SizedWord nT s = String -> Bool forall a. HasCallStack => String -> a error (String -> Bool) -> String -> Bool forall a b. (a -> b) -> a -> b $ String "Bits.testBit{" String -> ShowS forall a. [a] -> [a] -> [a] ++ SizedWord nT -> String forall nT. Natural nT => SizedWord nT -> String showSizedWordType SizedWord nT s String -> ShowS forall a. [a] -> [a] -> [a] ++ String "}: tried to test too large position" | Bool otherwise = Integer -> Int -> Bool forall a. Bits a => a -> Int -> Bool testBit Integer x Int b s :: SizedWord nT s@(SizedWord Integer x) shiftL :: SizedWord nT -> Int -> SizedWord nT `shiftL` Int b | Int b Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int 0 = String -> SizedWord nT forall a. HasCallStack => String -> a error (String -> SizedWord nT) -> String -> SizedWord nT forall a b. (a -> b) -> a -> b $ String "Bits.shiftL{" String -> ShowS forall a. [a] -> [a] -> [a] ++ SizedWord nT -> String forall nT. Natural nT => SizedWord nT -> String showSizedWordType SizedWord nT s String -> ShowS forall a. [a] -> [a] -> [a] ++ String "}: tried to shift by negative amount" | Bool otherwise = Integer -> SizedWord nT forall nT. Integer -> SizedWord nT SizedWord (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ Proxy nT -> Integer forall nT. Natural nT => Proxy nT -> Integer mask (Proxy nT forall a. Proxy a Proxy :: Proxy nT) Integer -> Integer -> Integer forall a. Bits a => a -> a -> a .&. (Integer x Integer -> Int -> Integer forall a. Bits a => a -> Int -> a `shiftL` Int b) s :: SizedWord nT s@(SizedWord Integer x) shiftR :: SizedWord nT -> Int -> SizedWord nT `shiftR` Int b | Int b Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int 0 = String -> SizedWord nT forall a. HasCallStack => String -> a error (String -> SizedWord nT) -> String -> SizedWord nT forall a b. (a -> b) -> a -> b $ String "Bits.shiftR{" String -> ShowS forall a. [a] -> [a] -> [a] ++ SizedWord nT -> String forall nT. Natural nT => SizedWord nT -> String showSizedWordType SizedWord nT s String -> ShowS forall a. [a] -> [a] -> [a] ++ String "}: tried to shift by negative amount" | Bool otherwise = Integer -> SizedWord nT forall nT. Integer -> SizedWord nT SizedWord (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ (Integer x Integer -> Int -> Integer forall a. Bits a => a -> Int -> a `shiftR` Int b) s :: SizedWord nT s@(SizedWord Integer x) rotateL :: SizedWord nT -> Int -> SizedWord nT `rotateL` Int b | Int b Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int 0 = String -> SizedWord nT forall a. HasCallStack => String -> a error (String -> SizedWord nT) -> String -> SizedWord nT forall a b. (a -> b) -> a -> b $ String "Bits.rotateL{" String -> ShowS forall a. [a] -> [a] -> [a] ++ SizedWord nT -> String forall nT. Natural nT => SizedWord nT -> String showSizedWordType SizedWord nT s String -> ShowS forall a. [a] -> [a] -> [a] ++ String "}: tried to rotate by negative amount" | Bool otherwise = Integer -> SizedWord nT forall nT. Integer -> SizedWord nT SizedWord (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ Proxy nT -> Integer forall nT. Natural nT => Proxy nT -> Integer mask (Proxy nT forall a. Proxy a Proxy :: Proxy nT) Integer -> Integer -> Integer forall a. Bits a => a -> a -> a .&. ((Integer x Integer -> Int -> Integer forall a. Bits a => a -> Int -> a `shiftL` Int b) Integer -> Integer -> Integer forall a. Bits a => a -> a -> a .|. (Integer x Integer -> Int -> Integer forall a. Bits a => a -> Int -> a `shiftR` (SizedWord nT -> Int forall a. Bits a => a -> Int bitSize SizedWord nT s Int -> Int -> Int forall a. Num a => a -> a -> a - Int b))) s :: SizedWord nT s@(SizedWord Integer x) rotateR :: SizedWord nT -> Int -> SizedWord nT `rotateR` Int b | Int b Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int 0 = String -> SizedWord nT forall a. HasCallStack => String -> a error (String -> SizedWord nT) -> String -> SizedWord nT forall a b. (a -> b) -> a -> b $ String "Bits.rotateR{" String -> ShowS forall a. [a] -> [a] -> [a] ++ SizedWord nT -> String forall nT. Natural nT => SizedWord nT -> String showSizedWordType SizedWord nT s String -> ShowS forall a. [a] -> [a] -> [a] ++ String "}: tried to rotate by negative amount" | Bool otherwise = Integer -> SizedWord nT forall nT. Integer -> SizedWord nT SizedWord (Integer -> SizedWord nT) -> Integer -> SizedWord nT forall a b. (a -> b) -> a -> b $ Proxy nT -> Integer forall nT. Natural nT => Proxy nT -> Integer mask (Proxy nT forall a. Proxy a Proxy :: Proxy nT) Integer -> Integer -> Integer forall a. Bits a => a -> a -> a .&. ((Integer x Integer -> Int -> Integer forall a. Bits a => a -> Int -> a `shiftR` Int b) Integer -> Integer -> Integer forall a. Bits a => a -> a -> a .|. (Integer x Integer -> Int -> Integer forall a. Bits a => a -> Int -> a `shiftL` (SizedWord nT -> Int forall a. Bits a => a -> Int bitSize SizedWord nT s Int -> Int -> Int forall a. Num a => a -> a -> a - Int b))) popCount :: SizedWord nT -> Int popCount (SizedWord Integer x) = Integer -> Int forall a. Bits a => a -> Int popCount Integer x bitSize :: SizedWord nT -> Int bitSize SizedWord nT _ = Proxy nT -> Int forall x y. (Integer x, Num y) => Proxy x -> y Num.fromInteger (Proxy nT forall a. Proxy a Proxy :: Proxy nT) isSigned :: SizedWord nT -> Bool isSigned SizedWord nT _ = Bool False showSizedWordTypeProxy :: forall nT. Num.Natural nT => Proxy nT -> String showSizedWordTypeProxy :: Proxy nT -> String showSizedWordTypeProxy Proxy nT n = String "SizedWord " String -> ShowS forall a. [a] -> [a] -> [a] ++ Integer -> String forall a. Show a => a -> String show (Proxy nT -> Integer forall x y. (Integer x, Num y) => Proxy x -> y Num.fromInteger Proxy nT n :: Integer) showSizedWordType :: forall nT. Num.Natural nT => SizedWord nT -> String showSizedWordType :: SizedWord nT -> String showSizedWordType SizedWord nT _ = Proxy nT -> String forall nT. Natural nT => Proxy nT -> String showSizedWordTypeProxy (Proxy nT forall a. Proxy a Proxy :: Proxy nT)