{-|
Module: Capnp.Bits
Description: Utilities for bitwhacking useful for capnproto.

This module provides misc. utilities for bitwhacking that are useful
in dealing with low-level details of the Cap'N Proto wire format.

This is mostly an implementation detail; users are unlikely to need
to use this module directly.
-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Capnp.Bits
    ( BitCount(..)
    , ByteCount(..)
    , WordCount(..)
    , Word1(..)
    , bitsToBytesCeil
    , bytesToWordsCeil
    , bytesToWordsFloor
    , wordsToBytes
    , lo, hi
    , i32, i30, i29
    , fromLo, fromHi
    , fromI32, fromI30, fromI29
    , bitRange
    , replaceBits
    )
  where

import Data.Bits
import Data.Int
import Data.Word

-- | Wrapper type for a quantity of bits. This along with 'ByteCount' and
-- 'WordCount' are helpful for avoiding mixing up units
newtype BitCount = BitCount Int
    deriving(Integer -> BitCount
BitCount -> BitCount
BitCount -> BitCount -> BitCount
(BitCount -> BitCount -> BitCount)
-> (BitCount -> BitCount -> BitCount)
-> (BitCount -> BitCount -> BitCount)
-> (BitCount -> BitCount)
-> (BitCount -> BitCount)
-> (BitCount -> BitCount)
-> (Integer -> BitCount)
-> Num BitCount
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> BitCount
$cfromInteger :: Integer -> BitCount
signum :: BitCount -> BitCount
$csignum :: BitCount -> BitCount
abs :: BitCount -> BitCount
$cabs :: BitCount -> BitCount
negate :: BitCount -> BitCount
$cnegate :: BitCount -> BitCount
* :: BitCount -> BitCount -> BitCount
$c* :: BitCount -> BitCount -> BitCount
- :: BitCount -> BitCount -> BitCount
$c- :: BitCount -> BitCount -> BitCount
+ :: BitCount -> BitCount -> BitCount
$c+ :: BitCount -> BitCount -> BitCount
Num, Num BitCount
Ord BitCount
Num BitCount
-> Ord BitCount -> (BitCount -> Rational) -> Real BitCount
BitCount -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: BitCount -> Rational
$ctoRational :: BitCount -> Rational
$cp2Real :: Ord BitCount
$cp1Real :: Num BitCount
Real, Enum BitCount
Real BitCount
Real BitCount
-> Enum BitCount
-> (BitCount -> BitCount -> BitCount)
-> (BitCount -> BitCount -> BitCount)
-> (BitCount -> BitCount -> BitCount)
-> (BitCount -> BitCount -> BitCount)
-> (BitCount -> BitCount -> (BitCount, BitCount))
-> (BitCount -> BitCount -> (BitCount, BitCount))
-> (BitCount -> Integer)
-> Integral BitCount
BitCount -> Integer
BitCount -> BitCount -> (BitCount, BitCount)
BitCount -> BitCount -> BitCount
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: BitCount -> Integer
$ctoInteger :: BitCount -> Integer
divMod :: BitCount -> BitCount -> (BitCount, BitCount)
$cdivMod :: BitCount -> BitCount -> (BitCount, BitCount)
quotRem :: BitCount -> BitCount -> (BitCount, BitCount)
$cquotRem :: BitCount -> BitCount -> (BitCount, BitCount)
mod :: BitCount -> BitCount -> BitCount
$cmod :: BitCount -> BitCount -> BitCount
div :: BitCount -> BitCount -> BitCount
$cdiv :: BitCount -> BitCount -> BitCount
rem :: BitCount -> BitCount -> BitCount
$crem :: BitCount -> BitCount -> BitCount
quot :: BitCount -> BitCount -> BitCount
$cquot :: BitCount -> BitCount -> BitCount
$cp2Integral :: Enum BitCount
$cp1Integral :: Real BitCount
Integral, Eq BitCount
BitCount
Eq BitCount
-> (BitCount -> BitCount -> BitCount)
-> (BitCount -> BitCount -> BitCount)
-> (BitCount -> BitCount -> BitCount)
-> (BitCount -> BitCount)
-> (BitCount -> Int -> BitCount)
-> (BitCount -> Int -> BitCount)
-> BitCount
-> (Int -> BitCount)
-> (BitCount -> Int -> BitCount)
-> (BitCount -> Int -> BitCount)
-> (BitCount -> Int -> BitCount)
-> (BitCount -> Int -> Bool)
-> (BitCount -> Maybe Int)
-> (BitCount -> Int)
-> (BitCount -> Bool)
-> (BitCount -> Int -> BitCount)
-> (BitCount -> Int -> BitCount)
-> (BitCount -> Int -> BitCount)
-> (BitCount -> Int -> BitCount)
-> (BitCount -> Int -> BitCount)
-> (BitCount -> Int -> BitCount)
-> (BitCount -> Int)
-> Bits BitCount
Int -> BitCount
BitCount -> Bool
BitCount -> Int
BitCount -> Maybe Int
BitCount -> BitCount
BitCount -> Int -> Bool
BitCount -> Int -> BitCount
BitCount -> BitCount -> BitCount
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: BitCount -> Int
$cpopCount :: BitCount -> Int
rotateR :: BitCount -> Int -> BitCount
$crotateR :: BitCount -> Int -> BitCount
rotateL :: BitCount -> Int -> BitCount
$crotateL :: BitCount -> Int -> BitCount
unsafeShiftR :: BitCount -> Int -> BitCount
$cunsafeShiftR :: BitCount -> Int -> BitCount
shiftR :: BitCount -> Int -> BitCount
$cshiftR :: BitCount -> Int -> BitCount
unsafeShiftL :: BitCount -> Int -> BitCount
$cunsafeShiftL :: BitCount -> Int -> BitCount
shiftL :: BitCount -> Int -> BitCount
$cshiftL :: BitCount -> Int -> BitCount
isSigned :: BitCount -> Bool
$cisSigned :: BitCount -> Bool
bitSize :: BitCount -> Int
$cbitSize :: BitCount -> Int
bitSizeMaybe :: BitCount -> Maybe Int
$cbitSizeMaybe :: BitCount -> Maybe Int
testBit :: BitCount -> Int -> Bool
$ctestBit :: BitCount -> Int -> Bool
complementBit :: BitCount -> Int -> BitCount
$ccomplementBit :: BitCount -> Int -> BitCount
clearBit :: BitCount -> Int -> BitCount
$cclearBit :: BitCount -> Int -> BitCount
setBit :: BitCount -> Int -> BitCount
$csetBit :: BitCount -> Int -> BitCount
bit :: Int -> BitCount
$cbit :: Int -> BitCount
zeroBits :: BitCount
$czeroBits :: BitCount
rotate :: BitCount -> Int -> BitCount
$crotate :: BitCount -> Int -> BitCount
shift :: BitCount -> Int -> BitCount
$cshift :: BitCount -> Int -> BitCount
complement :: BitCount -> BitCount
$ccomplement :: BitCount -> BitCount
xor :: BitCount -> BitCount -> BitCount
$cxor :: BitCount -> BitCount -> BitCount
.|. :: BitCount -> BitCount -> BitCount
$c.|. :: BitCount -> BitCount -> BitCount
.&. :: BitCount -> BitCount -> BitCount
$c.&. :: BitCount -> BitCount -> BitCount
$cp1Bits :: Eq BitCount
Bits, Eq BitCount
Eq BitCount
-> (BitCount -> BitCount -> Ordering)
-> (BitCount -> BitCount -> Bool)
-> (BitCount -> BitCount -> Bool)
-> (BitCount -> BitCount -> Bool)
-> (BitCount -> BitCount -> Bool)
-> (BitCount -> BitCount -> BitCount)
-> (BitCount -> BitCount -> BitCount)
-> Ord BitCount
BitCount -> BitCount -> Bool
BitCount -> BitCount -> Ordering
BitCount -> BitCount -> BitCount
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
min :: BitCount -> BitCount -> BitCount
$cmin :: BitCount -> BitCount -> BitCount
max :: BitCount -> BitCount -> BitCount
$cmax :: BitCount -> BitCount -> BitCount
>= :: BitCount -> BitCount -> Bool
$c>= :: BitCount -> BitCount -> Bool
> :: BitCount -> BitCount -> Bool
$c> :: BitCount -> BitCount -> Bool
<= :: BitCount -> BitCount -> Bool
$c<= :: BitCount -> BitCount -> Bool
< :: BitCount -> BitCount -> Bool
$c< :: BitCount -> BitCount -> Bool
compare :: BitCount -> BitCount -> Ordering
$ccompare :: BitCount -> BitCount -> Ordering
$cp1Ord :: Eq BitCount
Ord, BitCount -> BitCount -> Bool
(BitCount -> BitCount -> Bool)
-> (BitCount -> BitCount -> Bool) -> Eq BitCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BitCount -> BitCount -> Bool
$c/= :: BitCount -> BitCount -> Bool
== :: BitCount -> BitCount -> Bool
$c== :: BitCount -> BitCount -> Bool
Eq, Int -> BitCount
BitCount -> Int
BitCount -> [BitCount]
BitCount -> BitCount
BitCount -> BitCount -> [BitCount]
BitCount -> BitCount -> BitCount -> [BitCount]
(BitCount -> BitCount)
-> (BitCount -> BitCount)
-> (Int -> BitCount)
-> (BitCount -> Int)
-> (BitCount -> [BitCount])
-> (BitCount -> BitCount -> [BitCount])
-> (BitCount -> BitCount -> [BitCount])
-> (BitCount -> BitCount -> BitCount -> [BitCount])
-> Enum BitCount
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: BitCount -> BitCount -> BitCount -> [BitCount]
$cenumFromThenTo :: BitCount -> BitCount -> BitCount -> [BitCount]
enumFromTo :: BitCount -> BitCount -> [BitCount]
$cenumFromTo :: BitCount -> BitCount -> [BitCount]
enumFromThen :: BitCount -> BitCount -> [BitCount]
$cenumFromThen :: BitCount -> BitCount -> [BitCount]
enumFrom :: BitCount -> [BitCount]
$cenumFrom :: BitCount -> [BitCount]
fromEnum :: BitCount -> Int
$cfromEnum :: BitCount -> Int
toEnum :: Int -> BitCount
$ctoEnum :: Int -> BitCount
pred :: BitCount -> BitCount
$cpred :: BitCount -> BitCount
succ :: BitCount -> BitCount
$csucc :: BitCount -> BitCount
Enum, Int -> BitCount -> ShowS
[BitCount] -> ShowS
BitCount -> String
(Int -> BitCount -> ShowS)
-> (BitCount -> String) -> ([BitCount] -> ShowS) -> Show BitCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BitCount] -> ShowS
$cshowList :: [BitCount] -> ShowS
show :: BitCount -> String
$cshow :: BitCount -> String
showsPrec :: Int -> BitCount -> ShowS
$cshowsPrec :: Int -> BitCount -> ShowS
Show, BitCount
BitCount -> BitCount -> Bounded BitCount
forall a. a -> a -> Bounded a
maxBound :: BitCount
$cmaxBound :: BitCount
minBound :: BitCount
$cminBound :: BitCount
Bounded)

-- | A quantity of bytes
newtype ByteCount = ByteCount Int
    deriving(Integer -> ByteCount
ByteCount -> ByteCount
ByteCount -> ByteCount -> ByteCount
(ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount)
-> (ByteCount -> ByteCount)
-> (ByteCount -> ByteCount)
-> (Integer -> ByteCount)
-> Num ByteCount
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> ByteCount
$cfromInteger :: Integer -> ByteCount
signum :: ByteCount -> ByteCount
$csignum :: ByteCount -> ByteCount
abs :: ByteCount -> ByteCount
$cabs :: ByteCount -> ByteCount
negate :: ByteCount -> ByteCount
$cnegate :: ByteCount -> ByteCount
* :: ByteCount -> ByteCount -> ByteCount
$c* :: ByteCount -> ByteCount -> ByteCount
- :: ByteCount -> ByteCount -> ByteCount
$c- :: ByteCount -> ByteCount -> ByteCount
+ :: ByteCount -> ByteCount -> ByteCount
$c+ :: ByteCount -> ByteCount -> ByteCount
Num, Num ByteCount
Ord ByteCount
Num ByteCount
-> Ord ByteCount -> (ByteCount -> Rational) -> Real ByteCount
ByteCount -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: ByteCount -> Rational
$ctoRational :: ByteCount -> Rational
$cp2Real :: Ord ByteCount
$cp1Real :: Num ByteCount
Real, Enum ByteCount
Real ByteCount
Real ByteCount
-> Enum ByteCount
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> (ByteCount, ByteCount))
-> (ByteCount -> ByteCount -> (ByteCount, ByteCount))
-> (ByteCount -> Integer)
-> Integral ByteCount
ByteCount -> Integer
ByteCount -> ByteCount -> (ByteCount, ByteCount)
ByteCount -> ByteCount -> ByteCount
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: ByteCount -> Integer
$ctoInteger :: ByteCount -> Integer
divMod :: ByteCount -> ByteCount -> (ByteCount, ByteCount)
$cdivMod :: ByteCount -> ByteCount -> (ByteCount, ByteCount)
quotRem :: ByteCount -> ByteCount -> (ByteCount, ByteCount)
$cquotRem :: ByteCount -> ByteCount -> (ByteCount, ByteCount)
mod :: ByteCount -> ByteCount -> ByteCount
$cmod :: ByteCount -> ByteCount -> ByteCount
div :: ByteCount -> ByteCount -> ByteCount
$cdiv :: ByteCount -> ByteCount -> ByteCount
rem :: ByteCount -> ByteCount -> ByteCount
$crem :: ByteCount -> ByteCount -> ByteCount
quot :: ByteCount -> ByteCount -> ByteCount
$cquot :: ByteCount -> ByteCount -> ByteCount
$cp2Integral :: Enum ByteCount
$cp1Integral :: Real ByteCount
Integral, Eq ByteCount
ByteCount
Eq ByteCount
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount)
-> (ByteCount -> Int -> ByteCount)
-> (ByteCount -> Int -> ByteCount)
-> ByteCount
-> (Int -> ByteCount)
-> (ByteCount -> Int -> ByteCount)
-> (ByteCount -> Int -> ByteCount)
-> (ByteCount -> Int -> ByteCount)
-> (ByteCount -> Int -> Bool)
-> (ByteCount -> Maybe Int)
-> (ByteCount -> Int)
-> (ByteCount -> Bool)
-> (ByteCount -> Int -> ByteCount)
-> (ByteCount -> Int -> ByteCount)
-> (ByteCount -> Int -> ByteCount)
-> (ByteCount -> Int -> ByteCount)
-> (ByteCount -> Int -> ByteCount)
-> (ByteCount -> Int -> ByteCount)
-> (ByteCount -> Int)
-> Bits ByteCount
Int -> ByteCount
ByteCount -> Bool
ByteCount -> Int
ByteCount -> Maybe Int
ByteCount -> ByteCount
ByteCount -> Int -> Bool
ByteCount -> Int -> ByteCount
ByteCount -> ByteCount -> ByteCount
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: ByteCount -> Int
$cpopCount :: ByteCount -> Int
rotateR :: ByteCount -> Int -> ByteCount
$crotateR :: ByteCount -> Int -> ByteCount
rotateL :: ByteCount -> Int -> ByteCount
$crotateL :: ByteCount -> Int -> ByteCount
unsafeShiftR :: ByteCount -> Int -> ByteCount
$cunsafeShiftR :: ByteCount -> Int -> ByteCount
shiftR :: ByteCount -> Int -> ByteCount
$cshiftR :: ByteCount -> Int -> ByteCount
unsafeShiftL :: ByteCount -> Int -> ByteCount
$cunsafeShiftL :: ByteCount -> Int -> ByteCount
shiftL :: ByteCount -> Int -> ByteCount
$cshiftL :: ByteCount -> Int -> ByteCount
isSigned :: ByteCount -> Bool
$cisSigned :: ByteCount -> Bool
bitSize :: ByteCount -> Int
$cbitSize :: ByteCount -> Int
bitSizeMaybe :: ByteCount -> Maybe Int
$cbitSizeMaybe :: ByteCount -> Maybe Int
testBit :: ByteCount -> Int -> Bool
$ctestBit :: ByteCount -> Int -> Bool
complementBit :: ByteCount -> Int -> ByteCount
$ccomplementBit :: ByteCount -> Int -> ByteCount
clearBit :: ByteCount -> Int -> ByteCount
$cclearBit :: ByteCount -> Int -> ByteCount
setBit :: ByteCount -> Int -> ByteCount
$csetBit :: ByteCount -> Int -> ByteCount
bit :: Int -> ByteCount
$cbit :: Int -> ByteCount
zeroBits :: ByteCount
$czeroBits :: ByteCount
rotate :: ByteCount -> Int -> ByteCount
$crotate :: ByteCount -> Int -> ByteCount
shift :: ByteCount -> Int -> ByteCount
$cshift :: ByteCount -> Int -> ByteCount
complement :: ByteCount -> ByteCount
$ccomplement :: ByteCount -> ByteCount
xor :: ByteCount -> ByteCount -> ByteCount
$cxor :: ByteCount -> ByteCount -> ByteCount
.|. :: ByteCount -> ByteCount -> ByteCount
$c.|. :: ByteCount -> ByteCount -> ByteCount
.&. :: ByteCount -> ByteCount -> ByteCount
$c.&. :: ByteCount -> ByteCount -> ByteCount
$cp1Bits :: Eq ByteCount
Bits, Eq ByteCount
Eq ByteCount
-> (ByteCount -> ByteCount -> Ordering)
-> (ByteCount -> ByteCount -> Bool)
-> (ByteCount -> ByteCount -> Bool)
-> (ByteCount -> ByteCount -> Bool)
-> (ByteCount -> ByteCount -> Bool)
-> (ByteCount -> ByteCount -> ByteCount)
-> (ByteCount -> ByteCount -> ByteCount)
-> Ord ByteCount
ByteCount -> ByteCount -> Bool
ByteCount -> ByteCount -> Ordering
ByteCount -> ByteCount -> ByteCount
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
min :: ByteCount -> ByteCount -> ByteCount
$cmin :: ByteCount -> ByteCount -> ByteCount
max :: ByteCount -> ByteCount -> ByteCount
$cmax :: ByteCount -> ByteCount -> ByteCount
>= :: ByteCount -> ByteCount -> Bool
$c>= :: ByteCount -> ByteCount -> Bool
> :: ByteCount -> ByteCount -> Bool
$c> :: ByteCount -> ByteCount -> Bool
<= :: ByteCount -> ByteCount -> Bool
$c<= :: ByteCount -> ByteCount -> Bool
< :: ByteCount -> ByteCount -> Bool
$c< :: ByteCount -> ByteCount -> Bool
compare :: ByteCount -> ByteCount -> Ordering
$ccompare :: ByteCount -> ByteCount -> Ordering
$cp1Ord :: Eq ByteCount
Ord, ByteCount -> ByteCount -> Bool
(ByteCount -> ByteCount -> Bool)
-> (ByteCount -> ByteCount -> Bool) -> Eq ByteCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ByteCount -> ByteCount -> Bool
$c/= :: ByteCount -> ByteCount -> Bool
== :: ByteCount -> ByteCount -> Bool
$c== :: ByteCount -> ByteCount -> Bool
Eq, Int -> ByteCount
ByteCount -> Int
ByteCount -> [ByteCount]
ByteCount -> ByteCount
ByteCount -> ByteCount -> [ByteCount]
ByteCount -> ByteCount -> ByteCount -> [ByteCount]
(ByteCount -> ByteCount)
-> (ByteCount -> ByteCount)
-> (Int -> ByteCount)
-> (ByteCount -> Int)
-> (ByteCount -> [ByteCount])
-> (ByteCount -> ByteCount -> [ByteCount])
-> (ByteCount -> ByteCount -> [ByteCount])
-> (ByteCount -> ByteCount -> ByteCount -> [ByteCount])
-> Enum ByteCount
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ByteCount -> ByteCount -> ByteCount -> [ByteCount]
$cenumFromThenTo :: ByteCount -> ByteCount -> ByteCount -> [ByteCount]
enumFromTo :: ByteCount -> ByteCount -> [ByteCount]
$cenumFromTo :: ByteCount -> ByteCount -> [ByteCount]
enumFromThen :: ByteCount -> ByteCount -> [ByteCount]
$cenumFromThen :: ByteCount -> ByteCount -> [ByteCount]
enumFrom :: ByteCount -> [ByteCount]
$cenumFrom :: ByteCount -> [ByteCount]
fromEnum :: ByteCount -> Int
$cfromEnum :: ByteCount -> Int
toEnum :: Int -> ByteCount
$ctoEnum :: Int -> ByteCount
pred :: ByteCount -> ByteCount
$cpred :: ByteCount -> ByteCount
succ :: ByteCount -> ByteCount
$csucc :: ByteCount -> ByteCount
Enum, Int -> ByteCount -> ShowS
[ByteCount] -> ShowS
ByteCount -> String
(Int -> ByteCount -> ShowS)
-> (ByteCount -> String)
-> ([ByteCount] -> ShowS)
-> Show ByteCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ByteCount] -> ShowS
$cshowList :: [ByteCount] -> ShowS
show :: ByteCount -> String
$cshow :: ByteCount -> String
showsPrec :: Int -> ByteCount -> ShowS
$cshowsPrec :: Int -> ByteCount -> ShowS
Show, ByteCount
ByteCount -> ByteCount -> Bounded ByteCount
forall a. a -> a -> Bounded a
maxBound :: ByteCount
$cmaxBound :: ByteCount
minBound :: ByteCount
$cminBound :: ByteCount
Bounded)

-- | A quantity of 64-bit words
newtype WordCount = WordCount Int
    deriving(Integer -> WordCount
WordCount -> WordCount
WordCount -> WordCount -> WordCount
(WordCount -> WordCount -> WordCount)
-> (WordCount -> WordCount -> WordCount)
-> (WordCount -> WordCount -> WordCount)
-> (WordCount -> WordCount)
-> (WordCount -> WordCount)
-> (WordCount -> WordCount)
-> (Integer -> WordCount)
-> Num WordCount
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> WordCount
$cfromInteger :: Integer -> WordCount
signum :: WordCount -> WordCount
$csignum :: WordCount -> WordCount
abs :: WordCount -> WordCount
$cabs :: WordCount -> WordCount
negate :: WordCount -> WordCount
$cnegate :: WordCount -> WordCount
* :: WordCount -> WordCount -> WordCount
$c* :: WordCount -> WordCount -> WordCount
- :: WordCount -> WordCount -> WordCount
$c- :: WordCount -> WordCount -> WordCount
+ :: WordCount -> WordCount -> WordCount
$c+ :: WordCount -> WordCount -> WordCount
Num, Num WordCount
Ord WordCount
Num WordCount
-> Ord WordCount -> (WordCount -> Rational) -> Real WordCount
WordCount -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: WordCount -> Rational
$ctoRational :: WordCount -> Rational
$cp2Real :: Ord WordCount
$cp1Real :: Num WordCount
Real, Enum WordCount
Real WordCount
Real WordCount
-> Enum WordCount
-> (WordCount -> WordCount -> WordCount)
-> (WordCount -> WordCount -> WordCount)
-> (WordCount -> WordCount -> WordCount)
-> (WordCount -> WordCount -> WordCount)
-> (WordCount -> WordCount -> (WordCount, WordCount))
-> (WordCount -> WordCount -> (WordCount, WordCount))
-> (WordCount -> Integer)
-> Integral WordCount
WordCount -> Integer
WordCount -> WordCount -> (WordCount, WordCount)
WordCount -> WordCount -> WordCount
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: WordCount -> Integer
$ctoInteger :: WordCount -> Integer
divMod :: WordCount -> WordCount -> (WordCount, WordCount)
$cdivMod :: WordCount -> WordCount -> (WordCount, WordCount)
quotRem :: WordCount -> WordCount -> (WordCount, WordCount)
$cquotRem :: WordCount -> WordCount -> (WordCount, WordCount)
mod :: WordCount -> WordCount -> WordCount
$cmod :: WordCount -> WordCount -> WordCount
div :: WordCount -> WordCount -> WordCount
$cdiv :: WordCount -> WordCount -> WordCount
rem :: WordCount -> WordCount -> WordCount
$crem :: WordCount -> WordCount -> WordCount
quot :: WordCount -> WordCount -> WordCount
$cquot :: WordCount -> WordCount -> WordCount
$cp2Integral :: Enum WordCount
$cp1Integral :: Real WordCount
Integral, Eq WordCount
WordCount
Eq WordCount
-> (WordCount -> WordCount -> WordCount)
-> (WordCount -> WordCount -> WordCount)
-> (WordCount -> WordCount -> WordCount)
-> (WordCount -> WordCount)
-> (WordCount -> Int -> WordCount)
-> (WordCount -> Int -> WordCount)
-> WordCount
-> (Int -> WordCount)
-> (WordCount -> Int -> WordCount)
-> (WordCount -> Int -> WordCount)
-> (WordCount -> Int -> WordCount)
-> (WordCount -> Int -> Bool)
-> (WordCount -> Maybe Int)
-> (WordCount -> Int)
-> (WordCount -> Bool)
-> (WordCount -> Int -> WordCount)
-> (WordCount -> Int -> WordCount)
-> (WordCount -> Int -> WordCount)
-> (WordCount -> Int -> WordCount)
-> (WordCount -> Int -> WordCount)
-> (WordCount -> Int -> WordCount)
-> (WordCount -> Int)
-> Bits WordCount
Int -> WordCount
WordCount -> Bool
WordCount -> Int
WordCount -> Maybe Int
WordCount -> WordCount
WordCount -> Int -> Bool
WordCount -> Int -> WordCount
WordCount -> WordCount -> WordCount
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: WordCount -> Int
$cpopCount :: WordCount -> Int
rotateR :: WordCount -> Int -> WordCount
$crotateR :: WordCount -> Int -> WordCount
rotateL :: WordCount -> Int -> WordCount
$crotateL :: WordCount -> Int -> WordCount
unsafeShiftR :: WordCount -> Int -> WordCount
$cunsafeShiftR :: WordCount -> Int -> WordCount
shiftR :: WordCount -> Int -> WordCount
$cshiftR :: WordCount -> Int -> WordCount
unsafeShiftL :: WordCount -> Int -> WordCount
$cunsafeShiftL :: WordCount -> Int -> WordCount
shiftL :: WordCount -> Int -> WordCount
$cshiftL :: WordCount -> Int -> WordCount
isSigned :: WordCount -> Bool
$cisSigned :: WordCount -> Bool
bitSize :: WordCount -> Int
$cbitSize :: WordCount -> Int
bitSizeMaybe :: WordCount -> Maybe Int
$cbitSizeMaybe :: WordCount -> Maybe Int
testBit :: WordCount -> Int -> Bool
$ctestBit :: WordCount -> Int -> Bool
complementBit :: WordCount -> Int -> WordCount
$ccomplementBit :: WordCount -> Int -> WordCount
clearBit :: WordCount -> Int -> WordCount
$cclearBit :: WordCount -> Int -> WordCount
setBit :: WordCount -> Int -> WordCount
$csetBit :: WordCount -> Int -> WordCount
bit :: Int -> WordCount
$cbit :: Int -> WordCount
zeroBits :: WordCount
$czeroBits :: WordCount
rotate :: WordCount -> Int -> WordCount
$crotate :: WordCount -> Int -> WordCount
shift :: WordCount -> Int -> WordCount
$cshift :: WordCount -> Int -> WordCount
complement :: WordCount -> WordCount
$ccomplement :: WordCount -> WordCount
xor :: WordCount -> WordCount -> WordCount
$cxor :: WordCount -> WordCount -> WordCount
.|. :: WordCount -> WordCount -> WordCount
$c.|. :: WordCount -> WordCount -> WordCount
.&. :: WordCount -> WordCount -> WordCount
$c.&. :: WordCount -> WordCount -> WordCount
$cp1Bits :: Eq WordCount
Bits, Eq WordCount
Eq WordCount
-> (WordCount -> WordCount -> Ordering)
-> (WordCount -> WordCount -> Bool)
-> (WordCount -> WordCount -> Bool)
-> (WordCount -> WordCount -> Bool)
-> (WordCount -> WordCount -> Bool)
-> (WordCount -> WordCount -> WordCount)
-> (WordCount -> WordCount -> WordCount)
-> Ord WordCount
WordCount -> WordCount -> Bool
WordCount -> WordCount -> Ordering
WordCount -> WordCount -> WordCount
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
min :: WordCount -> WordCount -> WordCount
$cmin :: WordCount -> WordCount -> WordCount
max :: WordCount -> WordCount -> WordCount
$cmax :: WordCount -> WordCount -> WordCount
>= :: WordCount -> WordCount -> Bool
$c>= :: WordCount -> WordCount -> Bool
> :: WordCount -> WordCount -> Bool
$c> :: WordCount -> WordCount -> Bool
<= :: WordCount -> WordCount -> Bool
$c<= :: WordCount -> WordCount -> Bool
< :: WordCount -> WordCount -> Bool
$c< :: WordCount -> WordCount -> Bool
compare :: WordCount -> WordCount -> Ordering
$ccompare :: WordCount -> WordCount -> Ordering
$cp1Ord :: Eq WordCount
Ord, WordCount -> WordCount -> Bool
(WordCount -> WordCount -> Bool)
-> (WordCount -> WordCount -> Bool) -> Eq WordCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WordCount -> WordCount -> Bool
$c/= :: WordCount -> WordCount -> Bool
== :: WordCount -> WordCount -> Bool
$c== :: WordCount -> WordCount -> Bool
Eq, Int -> WordCount
WordCount -> Int
WordCount -> [WordCount]
WordCount -> WordCount
WordCount -> WordCount -> [WordCount]
WordCount -> WordCount -> WordCount -> [WordCount]
(WordCount -> WordCount)
-> (WordCount -> WordCount)
-> (Int -> WordCount)
-> (WordCount -> Int)
-> (WordCount -> [WordCount])
-> (WordCount -> WordCount -> [WordCount])
-> (WordCount -> WordCount -> [WordCount])
-> (WordCount -> WordCount -> WordCount -> [WordCount])
-> Enum WordCount
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: WordCount -> WordCount -> WordCount -> [WordCount]
$cenumFromThenTo :: WordCount -> WordCount -> WordCount -> [WordCount]
enumFromTo :: WordCount -> WordCount -> [WordCount]
$cenumFromTo :: WordCount -> WordCount -> [WordCount]
enumFromThen :: WordCount -> WordCount -> [WordCount]
$cenumFromThen :: WordCount -> WordCount -> [WordCount]
enumFrom :: WordCount -> [WordCount]
$cenumFrom :: WordCount -> [WordCount]
fromEnum :: WordCount -> Int
$cfromEnum :: WordCount -> Int
toEnum :: Int -> WordCount
$ctoEnum :: Int -> WordCount
pred :: WordCount -> WordCount
$cpred :: WordCount -> WordCount
succ :: WordCount -> WordCount
$csucc :: WordCount -> WordCount
Enum, Int -> WordCount -> ShowS
[WordCount] -> ShowS
WordCount -> String
(Int -> WordCount -> ShowS)
-> (WordCount -> String)
-> ([WordCount] -> ShowS)
-> Show WordCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WordCount] -> ShowS
$cshowList :: [WordCount] -> ShowS
show :: WordCount -> String
$cshow :: WordCount -> String
showsPrec :: Int -> WordCount -> ShowS
$cshowsPrec :: Int -> WordCount -> ShowS
Show, WordCount
WordCount -> WordCount -> Bounded WordCount
forall a. a -> a -> Bounded a
maxBound :: WordCount
$cmaxBound :: WordCount
minBound :: WordCount
$cminBound :: WordCount
Bounded)

-- | Convert bits to bytes. Rounds up.
bitsToBytesCeil :: BitCount -> ByteCount
bitsToBytesCeil :: BitCount -> ByteCount
bitsToBytesCeil (BitCount Int
n) = Int -> ByteCount
ByteCount ((Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
8)

-- | Convert bytes to words. Rounds up.
bytesToWordsCeil :: ByteCount -> WordCount
bytesToWordsCeil :: ByteCount -> WordCount
bytesToWordsCeil (ByteCount Int
n) = Int -> WordCount
WordCount ((Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
8)

-- | Convert bytes to words. Rounds down.
bytesToWordsFloor :: ByteCount -> WordCount
bytesToWordsFloor :: ByteCount -> WordCount
bytesToWordsFloor (ByteCount Int
n) = Int -> WordCount
WordCount (Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
8)

-- | Convert words to bytes.
wordsToBytes :: WordCount -> ByteCount
wordsToBytes :: WordCount -> ByteCount
wordsToBytes (WordCount Int
n) = Int -> ByteCount
ByteCount (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8)

-- | lo and hi extract the low and high 32 bits of a 64-bit word, respectively.
lo, hi :: Word64 -> Word32

-- | iN (where N is 32, 30, or 29) extracts the high N bits of its argument,
-- and treats them as a signed 32-bit integer.
i32, i30, i29 :: Word32 -> Int32

-- | fromLo and fromHi convert a 32-bit word to the low or high portion of
-- a 64-bit word. In general, @fromHi (hi w) .|. fromLo (lo w) == w@.
fromLo, fromHi :: Word32 -> Word64

-- | fromIN (where N is 32, 30, or 29) treats its argument as the high N bits of
-- a 32-bit word, returning the word. If @w < 2 ** N@ then @fromIN (iN w) == w@.
fromI32, fromI30, fromI29 :: Int32 -> Word32

lo :: Word64 -> Word32
lo Word64
w = Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR`  Int
0)
hi :: Word64 -> Word32
hi Word64
w = Word64 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
32)
i32 :: Word32 -> Int32
i32 = Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral
i30 :: Word32 -> Int32
i30 Word32
w = Word32 -> Int32
i32 Word32
w Int32 -> Int -> Int32
forall a. Bits a => a -> Int -> a
`shiftR` Int
2
i29 :: Word32 -> Int32
i29 Word32
w = Word32 -> Int32
i32 Word32
w Int32 -> Int -> Int32
forall a. Bits a => a -> Int -> a
`shiftR` Int
3

fromLo :: Word32 -> Word64
fromLo Word32
w = Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL`  Int
0
fromHi :: Word32 -> Word64
fromHi Word32
w = Word32 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
w Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
32
fromI32 :: Int32 -> Word32
fromI32 = Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral
fromI30 :: Int32 -> Word32
fromI30 Int32
w = Int32 -> Word32
fromI32 (Int32
w Int32 -> Int -> Int32
forall a. Bits a => a -> Int -> a
`shiftL` Int
2)
fromI29 :: Int32 -> Word32
fromI29 Int32
w = Int32 -> Word32
fromI32 (Int32
w Int32 -> Int -> Int32
forall a. Bits a => a -> Int -> a
`shiftL` Int
3)

-- | @bitRange word lo hi@ is the unsigned integer represented by the
-- bits of @word@ in the range [lo, hi)
bitRange :: (Integral a => Word64 -> Int -> Int -> a)
bitRange :: Word64 -> Int -> Int -> a
bitRange Word64
word Int
lo Int
hi = Word64 -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> a) -> Word64 -> a
forall a b. (a -> b) -> a -> b
$
    (Word64
word Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. ((Word64
1 Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
hi) Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
- Word64
1)) Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
lo

-- | @replaceBits new orig shift@ replaces the bits [shift, shift+N) in
-- @orig@ with the N bit integer @new@.
replaceBits :: (Bounded a, Integral a)
    => a -> Word64 -> Int -> Word64
replaceBits :: a -> Word64 -> Int -> Word64
replaceBits a
new Word64
orig Int
shift =
    (Word64
orig Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
mask) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. (a -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
new Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
shift)
  where
    mask :: Word64
mask = Word64 -> Word64
forall a. Bits a => a -> a
complement (Word64 -> Word64) -> Word64 -> Word64
forall a b. (a -> b) -> a -> b
$ a -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a
forall a. Bounded a => a
maxBound a -> a -> a
forall a. a -> a -> a
`asTypeOf` a
new) Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
shift

-- | 1 bit datatype, in the tradition of Word8, Word16 et al.
newtype Word1 = Word1 { Word1 -> Bool
word1ToBool :: Bool }
    deriving(Eq Word1
Eq Word1
-> (Word1 -> Word1 -> Ordering)
-> (Word1 -> Word1 -> Bool)
-> (Word1 -> Word1 -> Bool)
-> (Word1 -> Word1 -> Bool)
-> (Word1 -> Word1 -> Bool)
-> (Word1 -> Word1 -> Word1)
-> (Word1 -> Word1 -> Word1)
-> Ord Word1
Word1 -> Word1 -> Bool
Word1 -> Word1 -> Ordering
Word1 -> Word1 -> Word1
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
min :: Word1 -> Word1 -> Word1
$cmin :: Word1 -> Word1 -> Word1
max :: Word1 -> Word1 -> Word1
$cmax :: Word1 -> Word1 -> Word1
>= :: Word1 -> Word1 -> Bool
$c>= :: Word1 -> Word1 -> Bool
> :: Word1 -> Word1 -> Bool
$c> :: Word1 -> Word1 -> Bool
<= :: Word1 -> Word1 -> Bool
$c<= :: Word1 -> Word1 -> Bool
< :: Word1 -> Word1 -> Bool
$c< :: Word1 -> Word1 -> Bool
compare :: Word1 -> Word1 -> Ordering
$ccompare :: Word1 -> Word1 -> Ordering
$cp1Ord :: Eq Word1
Ord, Word1 -> Word1 -> Bool
(Word1 -> Word1 -> Bool) -> (Word1 -> Word1 -> Bool) -> Eq Word1
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Word1 -> Word1 -> Bool
$c/= :: Word1 -> Word1 -> Bool
== :: Word1 -> Word1 -> Bool
$c== :: Word1 -> Word1 -> Bool
Eq, Int -> Word1
Word1 -> Int
Word1 -> [Word1]
Word1 -> Word1
Word1 -> Word1 -> [Word1]
Word1 -> Word1 -> Word1 -> [Word1]
(Word1 -> Word1)
-> (Word1 -> Word1)
-> (Int -> Word1)
-> (Word1 -> Int)
-> (Word1 -> [Word1])
-> (Word1 -> Word1 -> [Word1])
-> (Word1 -> Word1 -> [Word1])
-> (Word1 -> Word1 -> Word1 -> [Word1])
-> Enum Word1
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Word1 -> Word1 -> Word1 -> [Word1]
$cenumFromThenTo :: Word1 -> Word1 -> Word1 -> [Word1]
enumFromTo :: Word1 -> Word1 -> [Word1]
$cenumFromTo :: Word1 -> Word1 -> [Word1]
enumFromThen :: Word1 -> Word1 -> [Word1]
$cenumFromThen :: Word1 -> Word1 -> [Word1]
enumFrom :: Word1 -> [Word1]
$cenumFrom :: Word1 -> [Word1]
fromEnum :: Word1 -> Int
$cfromEnum :: Word1 -> Int
toEnum :: Int -> Word1
$ctoEnum :: Int -> Word1
pred :: Word1 -> Word1
$cpred :: Word1 -> Word1
succ :: Word1 -> Word1
$csucc :: Word1 -> Word1
Enum, Word1
Word1 -> Word1 -> Bounded Word1
forall a. a -> a -> Bounded a
maxBound :: Word1
$cmaxBound :: Word1
minBound :: Word1
$cminBound :: Word1
Bounded, Eq Word1
Word1
Eq Word1
-> (Word1 -> Word1 -> Word1)
-> (Word1 -> Word1 -> Word1)
-> (Word1 -> Word1 -> Word1)
-> (Word1 -> Word1)
-> (Word1 -> Int -> Word1)
-> (Word1 -> Int -> Word1)
-> Word1
-> (Int -> Word1)
-> (Word1 -> Int -> Word1)
-> (Word1 -> Int -> Word1)
-> (Word1 -> Int -> Word1)
-> (Word1 -> Int -> Bool)
-> (Word1 -> Maybe Int)
-> (Word1 -> Int)
-> (Word1 -> Bool)
-> (Word1 -> Int -> Word1)
-> (Word1 -> Int -> Word1)
-> (Word1 -> Int -> Word1)
-> (Word1 -> Int -> Word1)
-> (Word1 -> Int -> Word1)
-> (Word1 -> Int -> Word1)
-> (Word1 -> Int)
-> Bits Word1
Int -> Word1
Word1 -> Bool
Word1 -> Int
Word1 -> Maybe Int
Word1 -> Word1
Word1 -> Int -> Bool
Word1 -> Int -> Word1
Word1 -> Word1 -> Word1
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: Word1 -> Int
$cpopCount :: Word1 -> Int
rotateR :: Word1 -> Int -> Word1
$crotateR :: Word1 -> Int -> Word1
rotateL :: Word1 -> Int -> Word1
$crotateL :: Word1 -> Int -> Word1
unsafeShiftR :: Word1 -> Int -> Word1
$cunsafeShiftR :: Word1 -> Int -> Word1
shiftR :: Word1 -> Int -> Word1
$cshiftR :: Word1 -> Int -> Word1
unsafeShiftL :: Word1 -> Int -> Word1
$cunsafeShiftL :: Word1 -> Int -> Word1
shiftL :: Word1 -> Int -> Word1
$cshiftL :: Word1 -> Int -> Word1
isSigned :: Word1 -> Bool
$cisSigned :: Word1 -> Bool
bitSize :: Word1 -> Int
$cbitSize :: Word1 -> Int
bitSizeMaybe :: Word1 -> Maybe Int
$cbitSizeMaybe :: Word1 -> Maybe Int
testBit :: Word1 -> Int -> Bool
$ctestBit :: Word1 -> Int -> Bool
complementBit :: Word1 -> Int -> Word1
$ccomplementBit :: Word1 -> Int -> Word1
clearBit :: Word1 -> Int -> Word1
$cclearBit :: Word1 -> Int -> Word1
setBit :: Word1 -> Int -> Word1
$csetBit :: Word1 -> Int -> Word1
bit :: Int -> Word1
$cbit :: Int -> Word1
zeroBits :: Word1
$czeroBits :: Word1
rotate :: Word1 -> Int -> Word1
$crotate :: Word1 -> Int -> Word1
shift :: Word1 -> Int -> Word1
$cshift :: Word1 -> Int -> Word1
complement :: Word1 -> Word1
$ccomplement :: Word1 -> Word1
xor :: Word1 -> Word1 -> Word1
$cxor :: Word1 -> Word1 -> Word1
.|. :: Word1 -> Word1 -> Word1
$c.|. :: Word1 -> Word1 -> Word1
.&. :: Word1 -> Word1 -> Word1
$c.&. :: Word1 -> Word1 -> Word1
$cp1Bits :: Eq Word1
Bits)

instance Num Word1 where
    + :: Word1 -> Word1 -> Word1
(+) = (Int -> Int -> Int) -> Word1 -> Word1 -> Word1
w1ThruEnum Int -> Int -> Int
forall a. Num a => a -> a -> a
(+)
    * :: Word1 -> Word1 -> Word1
(*) = (Int -> Int -> Int) -> Word1 -> Word1 -> Word1
w1ThruEnum Int -> Int -> Int
forall a. Num a => a -> a -> a
(*)
    abs :: Word1 -> Word1
abs = Word1 -> Word1
forall a. a -> a
id
    signum :: Word1 -> Word1
signum = Word1 -> Word1
forall a. a -> a
id
    negate :: Word1 -> Word1
negate = Word1 -> Word1
forall a. a -> a
id
    fromInteger :: Integer -> Word1
fromInteger Integer
x = Int -> Word1
forall a. Enum a => Int -> a
toEnum (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
x Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
2)

instance Real Word1 where
    toRational :: Word1 -> Rational
toRational = Int -> Rational
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Rational) -> (Word1 -> Int) -> Word1 -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word1 -> Int
forall a. Enum a => a -> Int
fromEnum

instance Integral Word1 where
    toInteger :: Word1 -> Integer
toInteger = Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> (Word1 -> Int) -> Word1 -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word1 -> Int
forall a. Enum a => a -> Int
fromEnum
    quotRem :: Word1 -> Word1 -> (Word1, Word1)
quotRem Word1
x Word1
y = let (Int
x', Int
y') = Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
quotRem (Word1 -> Int
forall a. Enum a => a -> Int
fromEnum Word1
x) (Word1 -> Int
forall a. Enum a => a -> Int
fromEnum Word1
y)
                  in (Int -> Word1
forall a. Enum a => Int -> a
toEnum Int
x', Int -> Word1
forall a. Enum a => Int -> a
toEnum Int
y')

instance Show Word1 where
    show :: Word1 -> String
show = Int -> String
forall a. Show a => a -> String
show (Int -> String) -> (Word1 -> Int) -> Word1 -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word1 -> Int
forall a. Enum a => a -> Int
fromEnum
    -- TODO: implement Read?

w1ThruEnum :: (Int -> Int -> Int) -> Word1 -> Word1 -> Word1
w1ThruEnum :: (Int -> Int -> Int) -> Word1 -> Word1 -> Word1
w1ThruEnum Int -> Int -> Int
op Word1
l Word1
r = Int -> Word1
forall a. Enum a => Int -> a
toEnum (Int -> Word1) -> Int -> Word1
forall a b. (a -> b) -> a -> b
$ (Word1 -> Int
forall a. Enum a => a -> Int
fromEnum Word1
l Int -> Int -> Int
`op` Word1 -> Int
forall a. Enum a => a -> Int
fromEnum Word1
r) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
2