{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Data.BitVector.Sized.Internal where
import Data.BitVector.Sized.Panic (panic)
import qualified Data.Bits as B
import qualified Data.Bits.Bitwise as B
import qualified Data.ByteString as BS
import qualified Numeric as N
import qualified Data.Parameterized.NatRepr as P
import qualified Prelude
import Control.DeepSeq (NFData)
import Data.Char (intToDigit)
import Data.List (genericLength)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Kind (Type)
import Data.Maybe (fromJust)
import Data.Word (Word8, Word16, Word32, Word64)
import Data.Parameterized ( NatRepr
, mkNatRepr
, natValue
, intValue
, addNat
, ShowF
, EqF(..)
, Hashable(..)
, Some(..)
, Pair(..)
)
import GHC.Generics (Generic)
import GHC.TypeLits (Nat, type(+), type(<=))
import Language.Haskell.TH.Lift (Lift)
import Numeric.Natural (Natural)
import Prelude hiding (abs, or, and, negate, concat, signum)
import System.Random.Stateful
checkNatRepr :: NatRepr w -> a -> a
checkNatRepr :: NatRepr w -> a -> a
checkNatRepr = Natural -> a -> a
forall a. Natural -> a -> a
checkNatural (Natural -> a -> a)
-> (NatRepr w -> Natural) -> NatRepr w -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue
checkNatural :: Natural -> a -> a
checkNatural :: Natural -> a -> a
checkNatural Natural
n a
a = if Natural
n Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
> (Int -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
forall a. Bounded a => a
maxBound :: Int) :: Natural)
then String -> [String] -> a
forall a. String -> [String] -> a
panic String
"Data.BitVector.Sized.Internal.checkNatural"
[Natural -> String
forall a. Show a => a -> String
show Natural
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" not representable as Int"]
else a
a
fromNatural :: Natural -> Int
fromNatural :: Natural -> Int
fromNatural = Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
data BV (w :: Nat) :: Type where
BV :: Integer -> BV w
deriving ( (forall x. BV w -> Rep (BV w) x)
-> (forall x. Rep (BV w) x -> BV w) -> Generic (BV w)
forall x. Rep (BV w) x -> BV w
forall x. BV w -> Rep (BV w) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (w :: Nat) x. Rep (BV w) x -> BV w
forall (w :: Nat) x. BV w -> Rep (BV w) x
$cto :: forall (w :: Nat) x. Rep (BV w) x -> BV w
$cfrom :: forall (w :: Nat) x. BV w -> Rep (BV w) x
Generic
, BV w -> ()
(BV w -> ()) -> NFData (BV w)
forall a. (a -> ()) -> NFData a
forall (w :: Nat). BV w -> ()
rnf :: BV w -> ()
$crnf :: forall (w :: Nat). BV w -> ()
NFData
, Int -> BV w -> String -> String
[BV w] -> String -> String
BV w -> String
(Int -> BV w -> String -> String)
-> (BV w -> String) -> ([BV w] -> String -> String) -> Show (BV w)
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
forall (w :: Nat). Int -> BV w -> String -> String
forall (w :: Nat). [BV w] -> String -> String
forall (w :: Nat). BV w -> String
showList :: [BV w] -> String -> String
$cshowList :: forall (w :: Nat). [BV w] -> String -> String
show :: BV w -> String
$cshow :: forall (w :: Nat). BV w -> String
showsPrec :: Int -> BV w -> String -> String
$cshowsPrec :: forall (w :: Nat). Int -> BV w -> String -> String
Show
, ReadPrec [BV w]
ReadPrec (BV w)
Int -> ReadS (BV w)
ReadS [BV w]
(Int -> ReadS (BV w))
-> ReadS [BV w]
-> ReadPrec (BV w)
-> ReadPrec [BV w]
-> Read (BV w)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall (w :: Nat). ReadPrec [BV w]
forall (w :: Nat). ReadPrec (BV w)
forall (w :: Nat). Int -> ReadS (BV w)
forall (w :: Nat). ReadS [BV w]
readListPrec :: ReadPrec [BV w]
$creadListPrec :: forall (w :: Nat). ReadPrec [BV w]
readPrec :: ReadPrec (BV w)
$creadPrec :: forall (w :: Nat). ReadPrec (BV w)
readList :: ReadS [BV w]
$creadList :: forall (w :: Nat). ReadS [BV w]
readsPrec :: Int -> ReadS (BV w)
$creadsPrec :: forall (w :: Nat). Int -> ReadS (BV w)
Read
, BV w -> BV w -> Bool
(BV w -> BV w -> Bool) -> (BV w -> BV w -> Bool) -> Eq (BV w)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (w :: Nat). BV w -> BV w -> Bool
/= :: BV w -> BV w -> Bool
$c/= :: forall (w :: Nat). BV w -> BV w -> Bool
== :: BV w -> BV w -> Bool
$c== :: forall (w :: Nat). BV w -> BV w -> Bool
Eq
, Ord
, BV w -> Q Exp
BV w -> Q (TExp (BV w))
(BV w -> Q Exp) -> (BV w -> Q (TExp (BV w))) -> Lift (BV w)
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
forall (w :: Nat). BV w -> Q Exp
forall (w :: Nat). BV w -> Q (TExp (BV w))
liftTyped :: BV w -> Q (TExp (BV w))
$cliftTyped :: forall (w :: Nat). BV w -> Q (TExp (BV w))
lift :: BV w -> Q Exp
$clift :: forall (w :: Nat). BV w -> Q Exp
Lift)
instance ShowF BV
instance EqF BV where
BV Integer
bv eqF :: BV a -> BV a -> Bool
`eqF` BV Integer
bv' = Integer
bv Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
bv'
instance Hashable (BV w) where
hashWithSalt :: Int -> BV w -> Int
hashWithSalt Int
salt (BV Integer
i) = Int -> Integer -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt Integer
i
mkBV' :: NatRepr w -> Integer -> BV w
mkBV' :: NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w Integer
x = Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (NatRepr w -> Integer -> Integer
forall (w :: Nat). NatRepr w -> Integer -> Integer
P.toUnsigned NatRepr w
w Integer
x)
mkBV :: NatRepr w
-> Integer
-> BV w
mkBV :: NatRepr w -> Integer -> BV w
mkBV NatRepr w
w Integer
x = NatRepr w -> BV w -> BV w
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr w
w (BV w -> BV w) -> BV w -> BV w
forall a b. (a -> b) -> a -> b
$ NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w Integer
x
checkUnsigned :: NatRepr w
-> Integer
-> Maybe Integer
checkUnsigned :: NatRepr w -> Integer -> Maybe Integer
checkUnsigned NatRepr w
w Integer
i = if Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 Bool -> Bool -> Bool
|| Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
P.maxUnsigned NatRepr w
w
then Maybe Integer
forall a. Maybe a
Nothing
else Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
i
mkBVUnsigned :: NatRepr w
-> Integer
-> Maybe (BV w)
mkBVUnsigned :: NatRepr w -> Integer -> Maybe (BV w)
mkBVUnsigned NatRepr w
w Integer
x = NatRepr w -> Maybe (BV w) -> Maybe (BV w)
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr w
w (Maybe (BV w) -> Maybe (BV w)) -> Maybe (BV w) -> Maybe (BV w)
forall a b. (a -> b) -> a -> b
$ Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer -> BV w) -> Maybe Integer -> Maybe (BV w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NatRepr w -> Integer -> Maybe Integer
forall (w :: Nat). NatRepr w -> Integer -> Maybe Integer
checkUnsigned NatRepr w
w Integer
x
signedToUnsigned :: 1 <= w => NatRepr w
-> Integer
-> Maybe Integer
signedToUnsigned :: NatRepr w -> Integer -> Maybe Integer
signedToUnsigned NatRepr w
w Integer
i = if Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< NatRepr w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> Integer
P.minSigned NatRepr w
w Bool -> Bool -> Bool
|| Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> NatRepr w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> Integer
P.maxSigned NatRepr w
w
then Maybe Integer
forall a. Maybe a
Nothing
else Integer -> Maybe Integer
forall a. a -> Maybe a
Just (Integer -> Maybe Integer) -> Integer -> Maybe Integer
forall a b. (a -> b) -> a -> b
$ if Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 then Integer
i Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
P.maxUnsigned NatRepr w
w Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
1 else Integer
i
mkBVSigned :: 1 <= w => NatRepr w
-> Integer
-> Maybe (BV w)
mkBVSigned :: NatRepr w -> Integer -> Maybe (BV w)
mkBVSigned NatRepr w
w Integer
x = NatRepr w -> Maybe (BV w) -> Maybe (BV w)
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr w
w (Maybe (BV w) -> Maybe (BV w)) -> Maybe (BV w) -> Maybe (BV w)
forall a b. (a -> b) -> a -> b
$ Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer -> BV w) -> Maybe Integer -> Maybe (BV w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NatRepr w -> Integer -> Maybe Integer
forall (w :: Nat).
(1 <= w) =>
NatRepr w -> Integer -> Maybe Integer
signedToUnsigned NatRepr w
w Integer
x
zero :: NatRepr w -> BV w
zero :: NatRepr w -> BV w
zero NatRepr w
w = NatRepr w -> BV w -> BV w
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr w
w (BV w -> BV w) -> BV w -> BV w
forall a b. (a -> b) -> a -> b
$ Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV Integer
0
one :: 1 <= w => NatRepr w -> BV w
one :: NatRepr w -> BV w
one NatRepr w
w = NatRepr w -> BV w -> BV w
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr w
w (BV w -> BV w) -> BV w -> BV w
forall a b. (a -> b) -> a -> b
$ Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV Integer
1
width :: NatRepr w -> BV w
width :: NatRepr w -> BV w
width NatRepr w
w = NatRepr w -> BV w -> BV w
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr w
w (BV w -> BV w) -> BV w -> BV w
forall a b. (a -> b) -> a -> b
$ Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
intValue NatRepr w
w)
minUnsigned :: NatRepr w -> BV w
minUnsigned :: NatRepr w -> BV w
minUnsigned NatRepr w
w = NatRepr w -> BV w -> BV w
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr w
w (BV w -> BV w) -> BV w -> BV w
forall a b. (a -> b) -> a -> b
$ Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV Integer
0
maxUnsigned :: NatRepr w -> BV w
maxUnsigned :: NatRepr w -> BV w
maxUnsigned NatRepr w
w = NatRepr w -> BV w -> BV w
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr w
w (BV w -> BV w) -> BV w -> BV w
forall a b. (a -> b) -> a -> b
$ Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
P.maxUnsigned NatRepr w
w)
minSigned :: 1 <= w => NatRepr w -> BV w
minSigned :: NatRepr w -> BV w
minSigned NatRepr w
w = NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV NatRepr w
w (NatRepr w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> Integer
P.minSigned NatRepr w
w)
maxSigned :: 1 <= w => NatRepr w -> BV w
maxSigned :: NatRepr w -> BV w
maxSigned NatRepr w
w = NatRepr w -> BV w -> BV w
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr w
w (BV w -> BV w) -> BV w -> BV w
forall a b. (a -> b) -> a -> b
$ Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (NatRepr w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> Integer
P.maxSigned NatRepr w
w)
unsignedClamp :: NatRepr w -> Integer -> BV w
unsignedClamp :: NatRepr w -> Integer -> BV w
unsignedClamp NatRepr w
w Integer
x = NatRepr w -> BV w -> BV w
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr w
w (BV w -> BV w) -> BV w -> BV w
forall a b. (a -> b) -> a -> b
$
if | Integer
x Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
P.minUnsigned NatRepr w
w -> Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
P.minUnsigned NatRepr w
w)
| Integer
x Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
P.maxUnsigned NatRepr w
w -> Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
P.maxUnsigned NatRepr w
w)
| Bool
otherwise -> Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV Integer
x
signedClamp :: 1 <= w => NatRepr w -> Integer -> BV w
signedClamp :: NatRepr w -> Integer -> BV w
signedClamp NatRepr w
w Integer
x = NatRepr w -> BV w -> BV w
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr w
w (BV w -> BV w) -> BV w -> BV w
forall a b. (a -> b) -> a -> b
$
if | Integer
x Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< NatRepr w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> Integer
P.minSigned NatRepr w
w -> NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (NatRepr w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> Integer
P.minSigned NatRepr w
w)
| Integer
x Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> NatRepr w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> Integer
P.maxSigned NatRepr w
w -> Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (NatRepr w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> Integer
P.maxSigned NatRepr w
w)
| Bool
otherwise -> NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w Integer
x
bool :: Bool -> BV 1
bool :: Bool -> BV 1
bool Bool
True = Integer -> BV 1
forall (w :: Nat). Integer -> BV w
BV Integer
1
bool Bool
False = Integer -> BV 1
forall (w :: Nat). Integer -> BV w
BV Integer
0
word8 :: Word8 -> BV 8
word8 :: Word8 -> BV 8
word8 = Integer -> BV 8
forall (w :: Nat). Integer -> BV w
BV (Integer -> BV 8) -> (Word8 -> Integer) -> Word8 -> BV 8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Integer
forall a. Integral a => a -> Integer
toInteger
word16 :: Word16 -> BV 16
word16 :: Word16 -> BV 16
word16 = Integer -> BV 16
forall (w :: Nat). Integer -> BV w
BV (Integer -> BV 16) -> (Word16 -> Integer) -> Word16 -> BV 16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Integer
forall a. Integral a => a -> Integer
toInteger
word32 :: Word32 -> BV 32
word32 :: Word32 -> BV 32
word32 = Integer -> BV 32
forall (w :: Nat). Integer -> BV w
BV (Integer -> BV 32) -> (Word32 -> Integer) -> Word32 -> BV 32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Integer
forall a. Integral a => a -> Integer
toInteger
word64 :: Word64 -> BV 64
word64 :: Word64 -> BV 64
word64 = Integer -> BV 64
forall (w :: Nat). Integer -> BV w
BV (Integer -> BV 64) -> (Word64 -> Integer) -> Word64 -> BV 64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Integer
forall a. Integral a => a -> Integer
toInteger
int8 :: Int8 -> BV 8
int8 :: Int8 -> BV 8
int8 = Word8 -> BV 8
word8 (Word8 -> BV 8) -> (Int8 -> Word8) -> Int8 -> BV 8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int8 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral :: Int8 -> Word8)
int16 :: Int16 -> BV 16
int16 :: Int16 -> BV 16
int16 = Word16 -> BV 16
word16 (Word16 -> BV 16) -> (Int16 -> Word16) -> Int16 -> BV 16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral :: Int16 -> Word16)
int32 :: Int32 -> BV 32
int32 :: Int32 -> BV 32
int32 = Word32 -> BV 32
word32 (Word32 -> BV 32) -> (Int32 -> Word32) -> Int32 -> BV 32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral :: Int32 -> Word32)
int64 :: Int64 -> BV 64
int64 :: Int64 -> BV 64
int64 = Word64 -> BV 64
word64 (Word64 -> BV 64) -> (Int64 -> Word64) -> Int64 -> BV 64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral :: Int64 -> Word64)
bitsBE :: [Bool] -> Pair NatRepr BV
bitsBE :: [Bool] -> Pair NatRepr BV
bitsBE [Bool]
bs = case Natural -> Some NatRepr
mkNatRepr (Integer -> Natural
forall a. Num a => Integer -> a
fromInteger ([Bool] -> Integer
forall i a. Num i => [a] -> i
genericLength [Bool]
bs)) of
Some NatRepr x
w -> NatRepr x -> Pair NatRepr BV -> Pair NatRepr BV
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr x
w (Pair NatRepr BV -> Pair NatRepr BV)
-> Pair NatRepr BV -> Pair NatRepr BV
forall a b. (a -> b) -> a -> b
$ NatRepr x -> BV x -> Pair NatRepr BV
forall k (a :: k -> *) (tp :: k) (b :: k -> *).
a tp -> b tp -> Pair a b
Pair NatRepr x
w (Integer -> BV x
forall (w :: Nat). Integer -> BV w
BV ([Bool] -> Integer
forall b. Bits b => [Bool] -> b
B.fromListBE [Bool]
bs))
bitsLE :: [Bool] -> Pair NatRepr BV
bitsLE :: [Bool] -> Pair NatRepr BV
bitsLE [Bool]
bs = case Natural -> Some NatRepr
mkNatRepr (Integer -> Natural
forall a. Num a => Integer -> a
fromInteger ([Bool] -> Integer
forall i a. Num i => [a] -> i
genericLength [Bool]
bs)) of
Some NatRepr x
w -> NatRepr x -> Pair NatRepr BV -> Pair NatRepr BV
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr x
w (Pair NatRepr BV -> Pair NatRepr BV)
-> Pair NatRepr BV -> Pair NatRepr BV
forall a b. (a -> b) -> a -> b
$ NatRepr x -> BV x -> Pair NatRepr BV
forall k (a :: k -> *) (tp :: k) (b :: k -> *).
a tp -> b tp -> Pair a b
Pair NatRepr x
w (Integer -> BV x
forall (w :: Nat). Integer -> BV w
BV ([Bool] -> Integer
forall b. Bits b => [Bool] -> b
B.fromListLE [Bool]
bs))
bytestringToIntegerBE :: BS.ByteString -> Integer
bytestringToIntegerBE :: ByteString -> Integer
bytestringToIntegerBE ByteString
bs
| Int
l Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Integer
0
| Int
l Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = Word8 -> Integer
forall a. Integral a => a -> Integer
toInteger (ByteString -> Word8
BS.head ByteString
bs)
| Bool
otherwise = Integer
x1 Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`B.shiftL` (Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8) Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
B..|. Integer
x2
where
l :: Int
l = ByteString -> Int
BS.length ByteString
bs
l1 :: Int
l1 = Int
l Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2
l2 :: Int
l2 = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
l1
(ByteString
bs1, ByteString
bs2) = Int -> ByteString -> (ByteString, ByteString)
BS.splitAt Int
l1 ByteString
bs
x1 :: Integer
x1 = ByteString -> Integer
bytestringToIntegerBE ByteString
bs1
x2 :: Integer
x2 = ByteString -> Integer
bytestringToIntegerBE ByteString
bs2
bytestringToIntegerLE :: BS.ByteString -> Integer
bytestringToIntegerLE :: ByteString -> Integer
bytestringToIntegerLE ByteString
bs
| Int
l Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Integer
0
| Int
l Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = Word8 -> Integer
forall a. Integral a => a -> Integer
toInteger (ByteString -> Word8
BS.head ByteString
bs)
| Bool
otherwise = Integer
x2 Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`B.shiftL` (Int
l1 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8) Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
B..|. Integer
x1
where
l :: Int
l = ByteString -> Int
BS.length ByteString
bs
l1 :: Int
l1 = Int
l Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2
(ByteString
bs1, ByteString
bs2) = Int -> ByteString -> (ByteString, ByteString)
BS.splitAt Int
l1 ByteString
bs
x1 :: Integer
x1 = ByteString -> Integer
bytestringToIntegerLE ByteString
bs1
x2 :: Integer
x2 = ByteString -> Integer
bytestringToIntegerLE ByteString
bs2
bytestringBE :: BS.ByteString -> Pair NatRepr BV
bytestringBE :: ByteString -> Pair NatRepr BV
bytestringBE ByteString
bs = case Natural -> Some NatRepr
mkNatRepr (Natural
8Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
*Int -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
BS.length ByteString
bs)) of
Some NatRepr x
w -> NatRepr x -> Pair NatRepr BV -> Pair NatRepr BV
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr x
w (Pair NatRepr BV -> Pair NatRepr BV)
-> Pair NatRepr BV -> Pair NatRepr BV
forall a b. (a -> b) -> a -> b
$ NatRepr x -> BV x -> Pair NatRepr BV
forall k (a :: k -> *) (tp :: k) (b :: k -> *).
a tp -> b tp -> Pair a b
Pair NatRepr x
w (Integer -> BV x
forall (w :: Nat). Integer -> BV w
BV (ByteString -> Integer
bytestringToIntegerBE ByteString
bs))
bytestringLE :: BS.ByteString -> Pair NatRepr BV
bytestringLE :: ByteString -> Pair NatRepr BV
bytestringLE ByteString
bs = case Natural -> Some NatRepr
mkNatRepr (Natural
8Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
*Int -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
BS.length ByteString
bs)) of
Some NatRepr x
w -> NatRepr x -> Pair NatRepr BV -> Pair NatRepr BV
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr x
w (Pair NatRepr BV -> Pair NatRepr BV)
-> Pair NatRepr BV -> Pair NatRepr BV
forall a b. (a -> b) -> a -> b
$ NatRepr x -> BV x -> Pair NatRepr BV
forall k (a :: k -> *) (tp :: k) (b :: k -> *).
a tp -> b tp -> Pair a b
Pair NatRepr x
w (Integer -> BV x
forall (w :: Nat). Integer -> BV w
BV (ByteString -> Integer
bytestringToIntegerLE ByteString
bs))
bytesBE :: [Word8] -> Pair NatRepr BV
bytesBE :: [Word8] -> Pair NatRepr BV
bytesBE = ByteString -> Pair NatRepr BV
bytestringBE (ByteString -> Pair NatRepr BV)
-> ([Word8] -> ByteString) -> [Word8] -> Pair NatRepr BV
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> ByteString
BS.pack
bytesLE :: [Word8] -> Pair NatRepr BV
bytesLE :: [Word8] -> Pair NatRepr BV
bytesLE = ByteString -> Pair NatRepr BV
bytestringLE (ByteString -> Pair NatRepr BV)
-> ([Word8] -> ByteString) -> [Word8] -> Pair NatRepr BV
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> ByteString
BS.pack
asUnsigned :: BV w -> Integer
asUnsigned :: BV w -> Integer
asUnsigned (BV Integer
x) = Integer
x
asSigned :: (1 <= w) => NatRepr w -> BV w -> Integer
asSigned :: NatRepr w -> BV w -> Integer
asSigned NatRepr w
w (BV Integer
x) =
let wInt :: Int
wInt = Natural -> Int
fromNatural (NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w
w) in
if Integer -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
B.testBit Integer
x (Int
wInt Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
then Integer
x Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Int -> Integer
forall a. Bits a => Int -> a
B.bit Int
wInt
else Integer
x
asNatural :: BV w -> Natural
asNatural :: BV w -> Natural
asNatural = (Integer -> Natural
forall a. Num a => Integer -> a
fromInteger :: Integer -> Natural) (Integer -> Natural) -> (BV w -> Integer) -> BV w -> Natural
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BV w -> Integer
forall (w :: Nat). BV w -> Integer
asUnsigned
asBitsBE :: NatRepr w -> BV w -> [Bool]
asBitsBE :: NatRepr w -> BV w -> [Bool]
asBitsBE NatRepr w
w BV w
bv = [ Natural -> BV w -> Bool
forall (w :: Nat). Natural -> BV w -> Bool
testBit' Natural
i BV w
bv | Natural
i <- Integer -> Natural
forall a. Num a => Integer -> a
fromInteger (Integer -> Natural) -> [Integer] -> [Natural]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Integer
wi Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1, Integer
wi Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
2 .. Integer
0] ]
where wi :: Integer
wi = NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
intValue NatRepr w
w
asBitsLE :: NatRepr w -> BV w -> [Bool]
asBitsLE :: NatRepr w -> BV w -> [Bool]
asBitsLE NatRepr w
w BV w
bv = [ Natural -> BV w -> Bool
forall (w :: Nat). Natural -> BV w -> Bool
testBit' Natural
i BV w
bv | Natural
i <- Integer -> Natural
forall a. Num a => Integer -> a
fromInteger (Integer -> Natural) -> [Integer] -> [Natural]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Integer
0 .. Integer
wi Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1] ]
where wi :: Integer
wi = NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
intValue NatRepr w
w
integerToBytesBE :: Natural
-> Integer
-> [Word8]
integerToBytesBE :: Natural -> Integer -> [Word8]
integerToBytesBE Natural
n Integer
x =
[ Integer -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
x Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`B.shiftR` (Int
8Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
ix)) | Int
ix <- [Int
niInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1, Int
niInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
2 .. Int
0] ]
where ni :: Int
ni = Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
n
integerToBytesLE :: Natural
-> Integer
-> [Word8]
integerToBytesLE :: Natural -> Integer -> [Word8]
integerToBytesLE Natural
n Integer
x =
[ Integer -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
x Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`B.shiftR` (Int
8Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
ix)) | Int
ix <- [Int
0 .. Int
niInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1] ]
where ni :: Int
ni = Natural -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
n
asBytesBE :: NatRepr w -> BV w -> Maybe [Word8]
asBytesBE :: NatRepr w -> BV w -> Maybe [Word8]
asBytesBE NatRepr w
w (BV Integer
x)
| NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w
w Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
`mod` Natural
8 Natural -> Natural -> Bool
forall a. Eq a => a -> a -> Bool
== Natural
0 = [Word8] -> Maybe [Word8]
forall a. a -> Maybe a
Just ([Word8] -> Maybe [Word8]) -> [Word8] -> Maybe [Word8]
forall a b. (a -> b) -> a -> b
$ Natural -> Integer -> [Word8]
integerToBytesBE (NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w
w Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
`div` Natural
8) Integer
x
| Bool
otherwise = Maybe [Word8]
forall a. Maybe a
Nothing
asBytesLE :: NatRepr w -> BV w -> Maybe [Word8]
asBytesLE :: NatRepr w -> BV w -> Maybe [Word8]
asBytesLE NatRepr w
w (BV Integer
x)
| NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w
w Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
`mod` Natural
8 Natural -> Natural -> Bool
forall a. Eq a => a -> a -> Bool
== Natural
0 = [Word8] -> Maybe [Word8]
forall a. a -> Maybe a
Just ([Word8] -> Maybe [Word8]) -> [Word8] -> Maybe [Word8]
forall a b. (a -> b) -> a -> b
$ Natural -> Integer -> [Word8]
integerToBytesLE (NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w
w Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
`div` Natural
8) Integer
x
| Bool
otherwise = Maybe [Word8]
forall a. Maybe a
Nothing
asBytestringBE :: NatRepr w -> BV w -> Maybe BS.ByteString
asBytestringBE :: NatRepr w -> BV w -> Maybe ByteString
asBytestringBE NatRepr w
w BV w
bv = [Word8] -> ByteString
BS.pack ([Word8] -> ByteString) -> Maybe [Word8] -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NatRepr w -> BV w -> Maybe [Word8]
forall (w :: Nat). NatRepr w -> BV w -> Maybe [Word8]
asBytesBE NatRepr w
w BV w
bv
asBytestringLE :: NatRepr w -> BV w -> Maybe BS.ByteString
asBytestringLE :: NatRepr w -> BV w -> Maybe ByteString
asBytestringLE NatRepr w
w BV w
bv = [Word8] -> ByteString
BS.pack ([Word8] -> ByteString) -> Maybe [Word8] -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NatRepr w -> BV w -> Maybe [Word8]
forall (w :: Nat). NatRepr w -> BV w -> Maybe [Word8]
asBytesLE NatRepr w
w BV w
bv
and :: BV w -> BV w -> BV w
and :: BV w -> BV w -> BV w
and (BV Integer
x) (BV Integer
y) = Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer
x Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
B..&. Integer
y)
or :: BV w -> BV w -> BV w
or :: BV w -> BV w -> BV w
or (BV Integer
x) (BV Integer
y) = Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer
x Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
B..|. Integer
y)
xor :: BV w -> BV w -> BV w
xor :: BV w -> BV w -> BV w
xor (BV Integer
x) (BV Integer
y) = Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer
x Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
`B.xor` Integer
y)
complement :: NatRepr w -> BV w -> BV w
complement :: NatRepr w -> BV w -> BV w
complement NatRepr w
w (BV Integer
x) = NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (Integer -> Integer
forall a. Bits a => a -> a
B.complement Integer
x)
shiftAmount :: NatRepr w -> Natural -> Int
shiftAmount :: NatRepr w -> Natural -> Int
shiftAmount NatRepr w
w Natural
shf = Natural -> Int
fromNatural (Natural -> Natural -> Natural
forall a. Ord a => a -> a -> a
min (NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w
w) Natural
shf)
shl :: NatRepr w -> BV w -> Natural -> BV w
shl :: NatRepr w -> BV w -> Natural -> BV w
shl NatRepr w
w (BV Integer
x) Natural
shf = NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (Integer
x Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`B.shiftL` NatRepr w -> Natural -> Int
forall (w :: Nat). NatRepr w -> Natural -> Int
shiftAmount NatRepr w
w Natural
shf)
ashr :: (1 <= w) => NatRepr w -> BV w -> Natural -> BV w
ashr :: NatRepr w -> BV w -> Natural -> BV w
ashr NatRepr w
w BV w
bv Natural
shf = NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`B.shiftR` NatRepr w -> Natural -> Int
forall (w :: Nat). NatRepr w -> Natural -> Int
shiftAmount NatRepr w
w Natural
shf)
lshr :: NatRepr w -> BV w -> Natural -> BV w
lshr :: NatRepr w -> BV w -> Natural -> BV w
lshr NatRepr w
w (BV Integer
x) Natural
shf =
Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer
x Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`B.shiftR` NatRepr w -> Natural -> Int
forall (w :: Nat). NatRepr w -> Natural -> Int
shiftAmount NatRepr w
w Natural
shf)
rotateL :: NatRepr w -> BV w -> Natural -> BV w
rotateL :: NatRepr w -> BV w -> Natural -> BV w
rotateL NatRepr w
w BV w
bv Natural
rot' = BV w
leftChunk BV w -> BV w -> BV w
forall (w :: Nat). BV w -> BV w -> BV w
`or` BV w
rightChunk
where rot :: Natural
rot = if Natural
wNatural Natural -> Natural -> Bool
forall a. Eq a => a -> a -> Bool
== Natural
0 then Natural
0 else Natural
rot' Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
`mod` Natural
wNatural
leftChunk :: BV w
leftChunk = NatRepr w -> BV w -> Natural -> BV w
forall (w :: Nat). NatRepr w -> BV w -> Natural -> BV w
shl NatRepr w
w BV w
bv Natural
rot
rightChunk :: BV w
rightChunk = NatRepr w -> BV w -> Natural -> BV w
forall (w :: Nat). NatRepr w -> BV w -> Natural -> BV w
lshr NatRepr w
w BV w
bv (Natural
wNatural Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
- Natural
rot)
wNatural :: Natural
wNatural = NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w
w
rotateR :: NatRepr w -> BV w -> Natural -> BV w
rotateR :: NatRepr w -> BV w -> Natural -> BV w
rotateR NatRepr w
w BV w
bv Natural
rot' = BV w
leftChunk BV w -> BV w -> BV w
forall (w :: Nat). BV w -> BV w -> BV w
`or` BV w
rightChunk
where rot :: Natural
rot = if Natural
wNatural Natural -> Natural -> Bool
forall a. Eq a => a -> a -> Bool
== Natural
0 then Natural
0 else Natural
rot' Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
`mod` Natural
wNatural
rightChunk :: BV w
rightChunk = NatRepr w -> BV w -> Natural -> BV w
forall (w :: Nat). NatRepr w -> BV w -> Natural -> BV w
lshr NatRepr w
w BV w
bv Natural
rot
leftChunk :: BV w
leftChunk = NatRepr w -> BV w -> Natural -> BV w
forall (w :: Nat). NatRepr w -> BV w -> Natural -> BV w
shl NatRepr w
w BV w
bv (Natural
wNatural Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
- Natural
rot)
wNatural :: Natural
wNatural = NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w
w
bit :: ix+1 <= w
=> NatRepr w
-> NatRepr ix
-> BV w
bit :: NatRepr w -> NatRepr ix -> BV w
bit NatRepr w
w NatRepr ix
ix =
NatRepr w -> BV w -> BV w
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr w
w (BV w -> BV w) -> BV w -> BV w
forall a b. (a -> b) -> a -> b
$
Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Int -> Integer
forall a. Bits a => Int -> a
B.bit (Natural -> Int
fromNatural (NatRepr ix -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr ix
ix)))
bit' :: NatRepr w
-> Natural
-> BV w
bit' :: NatRepr w -> Natural -> BV w
bit' NatRepr w
w Natural
ix
| Natural
ix Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
< NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w
w = NatRepr w -> BV w -> BV w
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr w
w (BV w -> BV w) -> BV w -> BV w
forall a b. (a -> b) -> a -> b
$ NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (Int -> Integer
forall a. Bits a => Int -> a
B.bit (Natural -> Int
fromNatural Natural
ix))
| Bool
otherwise = NatRepr w -> BV w
forall (w :: Nat). NatRepr w -> BV w
zero NatRepr w
w
setBit :: ix+1 <= w
=> NatRepr ix
-> BV w
-> BV w
setBit :: NatRepr ix -> BV w -> BV w
setBit NatRepr ix
ix BV w
bv =
BV w -> BV w -> BV w
forall (w :: Nat). BV w -> BV w -> BV w
or BV w
bv (Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Int -> Integer
forall a. Bits a => Int -> a
B.bit (Natural -> Int
fromNatural (NatRepr ix -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr ix
ix))))
setBit' :: NatRepr w
-> Natural
-> BV w
-> BV w
setBit' :: NatRepr w -> Natural -> BV w -> BV w
setBit' NatRepr w
w Natural
ix BV w
bv
| Natural
ix Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
< NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w
w = BV w -> BV w -> BV w
forall (w :: Nat). BV w -> BV w -> BV w
or BV w
bv (Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Int -> Integer
forall a. Bits a => Int -> a
B.bit (Natural -> Int
fromNatural Natural
ix)))
| Bool
otherwise = BV w
bv
clearBit :: ix+1 <= w
=> NatRepr w
-> NatRepr ix
-> BV w
-> BV w
clearBit :: NatRepr w -> NatRepr ix -> BV w -> BV w
clearBit NatRepr w
w NatRepr ix
ix BV w
bv =
BV w -> BV w -> BV w
forall (w :: Nat). BV w -> BV w -> BV w
and BV w
bv (NatRepr w -> BV w -> BV w
forall (w :: Nat). NatRepr w -> BV w -> BV w
complement NatRepr w
w (Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Int -> Integer
forall a. Bits a => Int -> a
B.bit (Natural -> Int
fromNatural (NatRepr ix -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr ix
ix)))))
clearBit' :: NatRepr w
-> Natural
-> BV w
-> BV w
clearBit' :: NatRepr w -> Natural -> BV w -> BV w
clearBit' NatRepr w
w Natural
ix BV w
bv
| Natural
ix Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
< NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w
w = BV w -> BV w -> BV w
forall (w :: Nat). BV w -> BV w -> BV w
and BV w
bv (NatRepr w -> BV w -> BV w
forall (w :: Nat). NatRepr w -> BV w -> BV w
complement NatRepr w
w (Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Int -> Integer
forall a. Bits a => Int -> a
B.bit (Natural -> Int
fromNatural Natural
ix))))
| Bool
otherwise = BV w
bv
complementBit :: ix+1 <= w
=> NatRepr ix
-> BV w
-> BV w
complementBit :: NatRepr ix -> BV w -> BV w
complementBit NatRepr ix
ix BV w
bv =
BV w -> BV w -> BV w
forall (w :: Nat). BV w -> BV w -> BV w
xor BV w
bv (Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Int -> Integer
forall a. Bits a => Int -> a
B.bit (Natural -> Int
fromNatural (NatRepr ix -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr ix
ix))))
complementBit' :: NatRepr w
-> Natural
-> BV w
-> BV w
complementBit' :: NatRepr w -> Natural -> BV w -> BV w
complementBit' NatRepr w
w Natural
ix BV w
bv
| Natural
ix Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
< NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w
w = BV w -> BV w -> BV w
forall (w :: Nat). BV w -> BV w -> BV w
xor BV w
bv (Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Int -> Integer
forall a. Bits a => Int -> a
B.bit (Natural -> Int
fromNatural Natural
ix)))
| Bool
otherwise = BV w
bv
testBit :: ix+1 <= w => NatRepr ix -> BV w -> Bool
testBit :: NatRepr ix -> BV w -> Bool
testBit NatRepr ix
ix (BV Integer
x) = Integer -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
B.testBit Integer
x (Natural -> Int
fromNatural (NatRepr ix -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr ix
ix))
testBit' :: Natural -> BV w -> Bool
testBit' :: Natural -> BV w -> Bool
testBit' Natural
ix (BV Integer
x)
| Natural
ix Natural -> Natural -> Bool
forall a. Ord a => a -> a -> Bool
> Int -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
forall a. Bounded a => a
maxBound :: Int) = Bool
False
| Bool
otherwise = Integer -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
B.testBit Integer
x (Natural -> Int
fromNatural Natural
ix)
popCount :: BV w -> BV w
popCount :: BV w -> BV w
popCount (BV Integer
x) = Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Integer -> Int
forall a. Bits a => a -> Int
B.popCount Integer
x))
ctz :: NatRepr w -> BV w -> BV w
ctz :: NatRepr w -> BV w -> BV w
ctz NatRepr w
w (BV Integer
x) = Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer -> Integer
go Integer
0)
where go :: Integer -> Integer
go !Integer
i | Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
intValue NatRepr w
w Bool -> Bool -> Bool
&&
Bool -> Bool
not (Integer -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
B.testBit Integer
x (Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
i)) = Integer -> Integer
go (Integer
iInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
1)
| Bool
otherwise = Integer
i
clz :: NatRepr w -> BV w -> BV w
clz :: NatRepr w -> BV w -> BV w
clz NatRepr w
w (BV Integer
x) = Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer -> Integer
go Integer
0)
where go :: Integer -> Integer
go !Integer
i | Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
intValue NatRepr w
w Bool -> Bool -> Bool
&&
Bool -> Bool
not (Integer -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
B.testBit Integer
x (Integer -> Int
forall a. Num a => Integer -> a
fromInteger (NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
intValue NatRepr w
w Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
i Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1))) =
Integer -> Integer
go (Integer
iInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
1)
| Bool
otherwise = Integer
i
truncBits :: Natural -> BV w -> BV w
truncBits :: Natural -> BV w -> BV w
truncBits Natural
b (BV Integer
x) = Natural -> BV w -> BV w
forall a. Natural -> a -> a
checkNatural Natural
b (BV w -> BV w) -> BV w -> BV w
forall a b. (a -> b) -> a -> b
$ Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer
x Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
B..&. (Int -> Integer
forall a. Bits a => Int -> a
B.bit (Natural -> Int
fromNatural Natural
b) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1))
add :: NatRepr w -> BV w -> BV w -> BV w
add :: NatRepr w -> BV w -> BV w -> BV w
add NatRepr w
w (BV Integer
x) (BV Integer
y) = NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (Integer
xInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
y)
sub :: NatRepr w -> BV w -> BV w -> BV w
sub :: NatRepr w -> BV w -> BV w -> BV w
sub NatRepr w
w (BV Integer
x) (BV Integer
y) = NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (Integer
xInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
y)
mul :: NatRepr w -> BV w -> BV w -> BV w
mul :: NatRepr w -> BV w -> BV w -> BV w
mul NatRepr w
w (BV Integer
x) (BV Integer
y) = NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (Integer
xInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
y)
uquot :: BV w -> BV w -> BV w
uquot :: BV w -> BV w -> BV w
uquot (BV Integer
x) (BV Integer
y) = Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer
x Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot` Integer
y)
urem :: BV w -> BV w -> BV w
urem :: BV w -> BV w -> BV w
urem (BV Integer
x) (BV Integer
y) = Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer
x Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`rem` Integer
y)
uquotRem :: BV w -> BV w -> (BV w, BV w)
uquotRem :: BV w -> BV w -> (BV w, BV w)
uquotRem BV w
bv1 BV w
bv2 = (BV w -> BV w -> BV w
forall (w :: Nat). BV w -> BV w -> BV w
uquot BV w
bv1 BV w
bv2, BV w -> BV w -> BV w
forall (w :: Nat). BV w -> BV w -> BV w
urem BV w
bv1 BV w
bv2)
squot :: (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
squot :: NatRepr w -> BV w -> BV w -> BV w
squot NatRepr w
w BV w
bv1 BV w
bv2 = NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (Integer
x Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`quot` Integer
y)
where x :: Integer
x = NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv1
y :: Integer
y = NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv2
srem :: (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
srem :: NatRepr w -> BV w -> BV w -> BV w
srem NatRepr w
w BV w
bv1 BV w
bv2 = NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (Integer
x Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`rem` Integer
y)
where x :: Integer
x = NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv1
y :: Integer
y = NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv2
squotRem :: (1 <= w) => NatRepr w -> BV w -> BV w -> (BV w, BV w)
squotRem :: NatRepr w -> BV w -> BV w -> (BV w, BV w)
squotRem NatRepr w
w BV w
bv1 BV w
bv2 = (NatRepr w -> BV w -> BV w -> BV w
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
squot NatRepr w
w BV w
bv1 BV w
bv2, NatRepr w -> BV w -> BV w -> BV w
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
srem NatRepr w
w BV w
bv1 BV w
bv2)
sdiv :: (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
sdiv :: NatRepr w -> BV w -> BV w -> BV w
sdiv NatRepr w
w BV w
bv1 BV w
bv2 = NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (Integer
x Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` Integer
y)
where x :: Integer
x = NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv1
y :: Integer
y = NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv2
smod :: (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
smod :: NatRepr w -> BV w -> BV w -> BV w
smod NatRepr w
w BV w
bv1 BV w
bv2 = NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (Integer
x Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`mod` Integer
y)
where x :: Integer
x = NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv1
y :: Integer
y = NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv2
sdivMod :: (1 <= w) => NatRepr w -> BV w -> BV w -> (BV w, BV w)
sdivMod :: NatRepr w -> BV w -> BV w -> (BV w, BV w)
sdivMod NatRepr w
w BV w
bv1 BV w
bv2 = (NatRepr w -> BV w -> BV w -> BV w
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
sdiv NatRepr w
w BV w
bv1 BV w
bv2, NatRepr w -> BV w -> BV w -> BV w
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
smod NatRepr w
w BV w
bv1 BV w
bv2)
abs :: (1 <= w) => NatRepr w -> BV w -> BV w
abs :: NatRepr w -> BV w -> BV w
abs NatRepr w
w BV w
bv = NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (Integer -> Integer
forall a. Num a => a -> a
Prelude.abs (NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv))
negate :: NatRepr w -> BV w -> BV w
negate :: NatRepr w -> BV w -> BV w
negate NatRepr w
w (BV Integer
x) = NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (-Integer
x)
signBit :: 1 <= w => NatRepr w -> BV w -> BV w
signBit :: NatRepr w -> BV w -> BV w
signBit NatRepr w
w bv :: BV w
bv@(BV Integer
_) = NatRepr w -> BV w -> Natural -> BV w
forall (w :: Nat). NatRepr w -> BV w -> Natural -> BV w
lshr NatRepr w
w BV w
bv (NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w
w Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
- Natural
1) BV w -> BV w -> BV w
forall (w :: Nat). BV w -> BV w -> BV w
`and` Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV Integer
1
signum :: 1 <= w => NatRepr w -> BV w -> BV w
signum :: NatRepr w -> BV w -> BV w
signum NatRepr w
w BV w
bv = NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (Integer -> Integer
forall a. Num a => a -> a
Prelude.signum (NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv))
slt :: (1 <= w) => NatRepr w -> BV w -> BV w -> Bool
slt :: NatRepr w -> BV w -> BV w -> Bool
slt NatRepr w
w BV w
bv1 BV w
bv2 = NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv2
sle :: (1 <= w) => NatRepr w -> BV w -> BV w -> Bool
sle :: NatRepr w -> BV w -> BV w -> Bool
sle NatRepr w
w BV w
bv1 BV w
bv2 = NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv2
ult :: BV w -> BV w -> Bool
ult :: BV w -> BV w -> Bool
ult BV w
bv1 BV w
bv2 = BV w -> Integer
forall (w :: Nat). BV w -> Integer
asUnsigned BV w
bv1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< BV w -> Integer
forall (w :: Nat). BV w -> Integer
asUnsigned BV w
bv2
ule :: BV w -> BV w -> Bool
ule :: BV w -> BV w -> Bool
ule BV w
bv1 BV w
bv2 = BV w -> Integer
forall (w :: Nat). BV w -> Integer
asUnsigned BV w
bv1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
<= BV w -> Integer
forall (w :: Nat). BV w -> Integer
asUnsigned BV w
bv2
umin :: BV w -> BV w -> BV w
umin :: BV w -> BV w -> BV w
umin (BV Integer
x) (BV Integer
y) = if Integer
x Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
y then Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV Integer
x else Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV Integer
y
umax :: BV w -> BV w -> BV w
umax :: BV w -> BV w -> BV w
umax (BV Integer
x) (BV Integer
y) = if Integer
x Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
y then Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV Integer
y else Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV Integer
x
smin :: (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
smin :: NatRepr w -> BV w -> BV w -> BV w
smin NatRepr w
w BV w
bv1 BV w
bv2 = if NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv2 then BV w
bv1 else BV w
bv2
smax :: (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
smax :: NatRepr w -> BV w -> BV w -> BV w
smax NatRepr w
w BV w
bv1 BV w
bv2 = if NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv1 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv2 then BV w
bv2 else BV w
bv1
concat :: NatRepr w
-> NatRepr w'
-> BV w
-> BV w'
-> BV (w+w')
concat :: NatRepr w -> NatRepr w' -> BV w -> BV w' -> BV (w + w')
concat NatRepr w
w NatRepr w'
w' (BV Integer
hi) (BV Integer
lo) = NatRepr (w + w') -> BV (w + w') -> BV (w + w')
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr (NatRepr w
w NatRepr w -> NatRepr w' -> NatRepr (w + w')
forall (m :: Nat) (n :: Nat).
NatRepr m -> NatRepr n -> NatRepr (m + n)
`addNat` NatRepr w'
w') (BV (w + w') -> BV (w + w')) -> BV (w + w') -> BV (w + w')
forall a b. (a -> b) -> a -> b
$
Integer -> BV (w + w')
forall (w :: Nat). Integer -> BV w
BV ((Integer
hi Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`B.shiftL` Natural -> Int
fromNatural (NatRepr w' -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w'
w')) Integer -> Integer -> Integer
forall a. Bits a => a -> a -> a
B..|. Integer
lo)
select :: ix + w' <= w
=> NatRepr ix
-> NatRepr w'
-> BV w
-> BV w'
select :: NatRepr ix -> NatRepr w' -> BV w -> BV w'
select NatRepr ix
ix NatRepr w'
w' (BV Integer
x) = NatRepr w' -> Integer -> BV w'
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w'
w' Integer
xShf
where xShf :: Integer
xShf = Integer
x Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`B.shiftR` Natural -> Int
fromNatural (NatRepr ix -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr ix
ix)
select' :: Natural
-> NatRepr w'
-> BV w
-> BV w'
select' :: Natural -> NatRepr w' -> BV w -> BV w'
select' Natural
ix NatRepr w'
w' (BV Integer
x)
| Natural -> Integer
forall a. Integral a => a -> Integer
toInteger Natural
ix 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) = NatRepr w' -> Integer -> BV w'
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV NatRepr w'
w' (Integer
x Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`B.shiftR` Natural -> Int
fromNatural Natural
ix)
| Bool
otherwise = NatRepr w' -> BV w'
forall (w :: Nat). NatRepr w -> BV w
zero NatRepr w'
w'
zext :: w + 1 <= w'
=> NatRepr w'
-> BV w
-> BV w'
zext :: NatRepr w' -> BV w -> BV w'
zext NatRepr w'
w (BV Integer
x) = NatRepr w' -> BV w' -> BV w'
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr NatRepr w'
w (BV w' -> BV w') -> BV w' -> BV w'
forall a b. (a -> b) -> a -> b
$ Integer -> BV w'
forall (w :: Nat). Integer -> BV w
BV Integer
x
sext :: (1 <= w, w + 1 <= w')
=> NatRepr w
-> NatRepr w'
-> BV w
-> BV w'
sext :: NatRepr w -> NatRepr w' -> BV w -> BV w'
sext NatRepr w
w NatRepr w'
w' BV w
bv = NatRepr w' -> Integer -> BV w'
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV NatRepr w'
w' (NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv)
trunc :: w' + 1 <= w
=> NatRepr w'
-> BV w
-> BV w'
trunc :: NatRepr w' -> BV w -> BV w'
trunc NatRepr w'
w' (BV Integer
x) = NatRepr w' -> Integer -> BV w'
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w'
w' Integer
x
trunc' :: NatRepr w'
-> BV w
-> BV w'
trunc' :: NatRepr w' -> BV w -> BV w'
trunc' NatRepr w'
w' (BV Integer
x) = NatRepr w' -> Integer -> BV w'
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV NatRepr w'
w' Integer
x
mulWide :: NatRepr w -> NatRepr w' -> BV w -> BV w' -> BV (w+w')
mulWide :: NatRepr w -> NatRepr w' -> BV w -> BV w' -> BV (w + w')
mulWide NatRepr w
w NatRepr w'
w' (BV Integer
x) (BV Integer
y) = NatRepr (w + w') -> BV (w + w') -> BV (w + w')
forall (w :: Nat) a. NatRepr w -> a -> a
checkNatRepr (NatRepr w
w NatRepr w -> NatRepr w' -> NatRepr (w + w')
forall (m :: Nat) (n :: Nat).
NatRepr m -> NatRepr n -> NatRepr (m + n)
`addNat` NatRepr w'
w') (BV (w + w') -> BV (w + w')) -> BV (w + w') -> BV (w + w')
forall a b. (a -> b) -> a -> b
$ Integer -> BV (w + w')
forall (w :: Nat). Integer -> BV w
BV (Integer
xInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
y)
succUnsigned :: NatRepr w -> BV w -> Maybe (BV w)
succUnsigned :: NatRepr w -> BV w -> Maybe (BV w)
succUnsigned NatRepr w
w (BV Integer
x) =
if Integer
x Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
P.maxUnsigned NatRepr w
w
then Maybe (BV w)
forall a. Maybe a
Nothing
else BV w -> Maybe (BV w)
forall a. a -> Maybe a
Just (Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer
xInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
1))
succSigned :: 1 <= w => NatRepr w -> BV w -> Maybe (BV w)
succSigned :: NatRepr w -> BV w -> Maybe (BV w)
succSigned NatRepr w
w (BV Integer
x) =
if Integer
x Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== NatRepr w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> Integer
P.maxSigned NatRepr w
w
then Maybe (BV w)
forall a. Maybe a
Nothing
else BV w -> Maybe (BV w)
forall a. a -> Maybe a
Just (NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (Integer
xInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
1))
predUnsigned :: NatRepr w -> BV w -> Maybe (BV w)
predUnsigned :: NatRepr w -> BV w -> Maybe (BV w)
predUnsigned NatRepr w
w (BV Integer
x) =
if Integer
x Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
P.minUnsigned NatRepr w
w
then Maybe (BV w)
forall a. Maybe a
Nothing
else BV w -> Maybe (BV w)
forall a. a -> Maybe a
Just (Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer
xInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
1))
predSigned :: 1 <= w => NatRepr w -> BV w -> Maybe (BV w)
predSigned :: NatRepr w -> BV w -> Maybe (BV w)
predSigned NatRepr w
w bv :: BV w
bv@(BV Integer
x) =
if BV w
bv BV w -> BV w -> Bool
forall a. Eq a => a -> a -> Bool
== NatRepr w -> BV w
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w
minSigned NatRepr w
w
then Maybe (BV w)
forall a. Maybe a
Nothing
else BV w -> Maybe (BV w)
forall a. a -> Maybe a
Just (NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV' NatRepr w
w (Integer
xInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
1))
enumFromToUnsigned :: BV w
-> BV w
-> [BV w]
enumFromToUnsigned :: BV w -> BV w -> [BV w]
enumFromToUnsigned BV w
bv1 BV w
bv2 = Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer -> BV w) -> [Integer] -> [BV w]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [BV w -> Integer
forall (w :: Nat). BV w -> Integer
asUnsigned BV w
bv1 .. BV w -> Integer
forall (w :: Nat). BV w -> Integer
asUnsigned BV w
bv2]
enumFromToSigned :: 1 <= w => NatRepr w
-> BV w
-> BV w
-> [BV w]
enumFromToSigned :: NatRepr w -> BV w -> BV w -> [BV w]
enumFromToSigned NatRepr w
w BV w
bv1 BV w
bv2 =
Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer -> BV w) -> (Integer -> Integer) -> Integer -> BV w
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Integer -> Integer
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Integer -> Integer)
-> (Integer -> Maybe Integer) -> Integer -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NatRepr w -> Integer -> Maybe Integer
forall (w :: Nat).
(1 <= w) =>
NatRepr w -> Integer -> Maybe Integer
signedToUnsigned NatRepr w
w (Integer -> BV w) -> [Integer] -> [BV w]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv1 .. NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
bv2]
uniformM :: StatefulGen g m => NatRepr w -> g -> m (BV w)
uniformM :: NatRepr w -> g -> m (BV w)
uniformM NatRepr w
w g
g = Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer -> BV w) -> m Integer -> m (BV w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Integer, Integer) -> g -> m Integer
forall a g (m :: * -> *).
(UniformRange a, StatefulGen g m) =>
(a, a) -> g -> m a
uniformRM (NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
P.minUnsigned NatRepr w
w, NatRepr w -> Integer
forall (w :: Nat). NatRepr w -> Integer
P.maxUnsigned NatRepr w
w) g
g
uUniformRM :: StatefulGen g m => (BV w, BV w) -> g -> m (BV w)
uUniformRM :: (BV w, BV w) -> g -> m (BV w)
uUniformRM (BV w
lo, BV w
hi) g
g =
let loI :: Integer
loI = BV w -> Integer
forall (w :: Nat). BV w -> Integer
asUnsigned BV w
lo
hiI :: Integer
hiI = BV w -> Integer
forall (w :: Nat). BV w -> Integer
asUnsigned BV w
hi
in Integer -> BV w
forall (w :: Nat). Integer -> BV w
BV (Integer -> BV w) -> m Integer -> m (BV w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Integer, Integer) -> g -> m Integer
forall a g (m :: * -> *).
(UniformRange a, StatefulGen g m) =>
(a, a) -> g -> m a
uniformRM (Integer
loI, Integer
hiI) g
g
sUniformRM :: (StatefulGen g m, 1 <= w) => NatRepr w -> (BV w, BV w) -> g -> m (BV w)
sUniformRM :: NatRepr w -> (BV w, BV w) -> g -> m (BV w)
sUniformRM NatRepr w
w (BV w
lo, BV w
hi) g
g =
let loI :: Integer
loI = NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
lo
hiI :: Integer
hiI = NatRepr w -> BV w -> Integer
forall (w :: Nat). (1 <= w) => NatRepr w -> BV w -> Integer
asSigned NatRepr w
w BV w
hi
in NatRepr w -> Integer -> BV w
forall (w :: Nat). NatRepr w -> Integer -> BV w
mkBV NatRepr w
w (Integer -> BV w) -> m Integer -> m (BV w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Integer, Integer) -> g -> m Integer
forall a g (m :: * -> *).
(UniformRange a, StatefulGen g m) =>
(a, a) -> g -> m a
uniformRM (Integer
loI, Integer
hiI) g
g
ppHex :: NatRepr w -> BV w -> String
ppHex :: NatRepr w -> BV w -> String
ppHex NatRepr w
w (BV Integer
x) = String
"0x" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String -> String
forall a. (Integral a, Show a) => a -> String -> String
N.showHex Integer
x String
"" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":" String -> String -> String
forall a. [a] -> [a] -> [a]
++ NatRepr w -> String
forall (w :: Nat). NatRepr w -> String
ppWidth NatRepr w
w
ppBin :: NatRepr w -> BV w -> String
ppBin :: NatRepr w -> BV w -> String
ppBin NatRepr w
w (BV Integer
x) = String
"0b" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> (Int -> Char) -> Integer -> String -> String
forall a.
(Integral a, Show a) =>
a -> (Int -> Char) -> a -> String -> String
N.showIntAtBase Integer
2 Int -> Char
intToDigit Integer
x String
"" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":" String -> String -> String
forall a. [a] -> [a] -> [a]
++ NatRepr w -> String
forall (w :: Nat). NatRepr w -> String
ppWidth NatRepr w
w
ppOct :: NatRepr w -> BV w -> String
ppOct :: NatRepr w -> BV w -> String
ppOct NatRepr w
w (BV Integer
x) = String
"0o" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String -> String
forall a. (Integral a, Show a) => a -> String -> String
N.showOct Integer
x String
"" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":" String -> String -> String
forall a. [a] -> [a] -> [a]
++ NatRepr w -> String
forall (w :: Nat). NatRepr w -> String
ppWidth NatRepr w
w
ppDec :: NatRepr w -> BV w -> String
ppDec :: NatRepr w -> BV w -> String
ppDec NatRepr w
w (BV Integer
x) = Integer -> String
forall a. Show a => a -> String
show Integer
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":" String -> String -> String
forall a. [a] -> [a] -> [a]
++ NatRepr w -> String
forall (w :: Nat). NatRepr w -> String
ppWidth NatRepr w
w
ppWidth :: NatRepr w -> String
ppWidth :: NatRepr w -> String
ppWidth NatRepr w
w = String
"[" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Natural -> String
forall a. Show a => a -> String
show (NatRepr w -> Natural
forall (n :: Nat). NatRepr n -> Natural
natValue NatRepr w
w) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"]"