{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# 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 as Prelude
import Data.Char (intToDigit)
import Data.List (genericLength)
import Data.Int
import Data.Kind (Type)
import Data.Maybe (fromJust)
import Data.Word
import Data.Parameterized ( NatRepr
, mkNatRepr
, natValue
, intValue
, addNat
, ShowF
, EqF(..)
, Hashable(..)
, Some(..)
, Pair(..)
)
import GHC.Generics
import GHC.TypeLits
import Language.Haskell.TH.Lift (Lift)
import Numeric.Natural
import Prelude hiding (abs, or, and, negate, concat, signum)
checkNatRepr :: NatRepr w -> a -> a
checkNatRepr = checkNatural . natValue
checkNatural :: Natural -> a -> a
checkNatural n a = if n > (fromIntegral (maxBound :: Int) :: Natural)
then panic "Data.BitVector.Sized.Internal.checkNatural"
[show n ++ " not representable as Int"]
else a
fromNatural :: Natural -> Int
fromNatural = fromIntegral
data BV (w :: Nat) :: Type where
BV :: Integer -> BV w
deriving ( Generic
, Show
, Read
, Eq
, Ord
, Lift)
instance ShowF BV
instance EqF BV where
BV bv `eqF` BV bv' = bv == bv'
instance Hashable (BV w) where
hashWithSalt salt (BV i) = hashWithSalt salt i
mkBV' :: NatRepr w -> Integer -> BV w
mkBV' w x = BV (P.toUnsigned w x)
mkBV :: NatRepr w
-> Integer
-> BV w
mkBV w x = checkNatRepr w $ mkBV' w x
checkUnsigned :: NatRepr w
-> Integer
-> Maybe Integer
checkUnsigned w i = if i < 0 || i > P.maxUnsigned w
then Nothing
else Just i
mkBVUnsigned :: NatRepr w
-> Integer
-> Maybe (BV w)
mkBVUnsigned w x = checkNatRepr w $ BV <$> checkUnsigned w x
signedToUnsigned :: 1 <= w => NatRepr w
-> Integer
-> Maybe Integer
signedToUnsigned w i = if i < P.minSigned w || i > P.maxSigned w
then Nothing
else Just $ if i < 0 then i + P.maxUnsigned w + 1 else i
mkBVSigned :: 1 <= w => NatRepr w
-> Integer
-> Maybe (BV w)
mkBVSigned w x = checkNatRepr w $ BV <$> signedToUnsigned w x
zero :: NatRepr w -> BV w
zero w = checkNatRepr w $ BV 0
one :: 1 <= w => NatRepr w -> BV w
one w = checkNatRepr w $ BV 1
width :: NatRepr w -> BV w
width w = checkNatRepr w $ BV (intValue w)
minUnsigned :: NatRepr w -> BV w
minUnsigned w = checkNatRepr w $ BV 0
maxUnsigned :: NatRepr w -> BV w
maxUnsigned w = checkNatRepr w $ BV (P.maxUnsigned w)
minSigned :: 1 <= w => NatRepr w -> BV w
minSigned w = mkBV w (P.minSigned w)
maxSigned :: 1 <= w => NatRepr w -> BV w
maxSigned w = checkNatRepr w $ BV (P.maxSigned w)
unsignedClamp :: NatRepr w -> Integer -> BV w
unsignedClamp w x = checkNatRepr w $
if | x < P.minUnsigned w -> BV (P.minUnsigned w)
| x > P.maxUnsigned w -> BV (P.maxUnsigned w)
| otherwise -> BV x
signedClamp :: 1 <= w => NatRepr w -> Integer -> BV w
signedClamp w x = checkNatRepr w $
if | x < P.minSigned w -> mkBV' w (P.minSigned w)
| x > P.maxSigned w -> BV (P.maxSigned w)
| otherwise -> mkBV' w x
bool :: Bool -> BV 1
bool True = BV 1
bool False = BV 0
word8 :: Word8 -> BV 8
word8 = BV . toInteger
word16 :: Word16 -> BV 16
word16 = BV . toInteger
word32 :: Word32 -> BV 32
word32 = BV . toInteger
word64 :: Word64 -> BV 64
word64 = BV . toInteger
int8 :: Int8 -> BV 8
int8 = word8 . (fromIntegral :: Int8 -> Word8)
int16 :: Int16 -> BV 16
int16 = word16 . (fromIntegral :: Int16 -> Word16)
int32 :: Int32 -> BV 32
int32 = word32 . (fromIntegral :: Int32 -> Word32)
int64 :: Int64 -> BV 64
int64 = word64 . (fromIntegral :: Int64 -> Word64)
bitsBE :: [Bool] -> Pair NatRepr BV
bitsBE bs = case mkNatRepr (fromInteger (genericLength bs)) of
Some w -> checkNatRepr w $ Pair w (BV (B.fromListBE bs))
bitsLE :: [Bool] -> Pair NatRepr BV
bitsLE bs = case mkNatRepr (fromInteger (genericLength bs)) of
Some w -> checkNatRepr w $ Pair w (BV (B.fromListLE bs))
bytestringToIntegerBE :: BS.ByteString -> Integer
bytestringToIntegerBE bs
| l == 0 = 0
| l == 1 = toInteger (BS.head bs)
| otherwise = x1 `B.shiftL` (l2 * 8) B..|. x2
where
l = BS.length bs
l1 = l `div` 2
l2 = l - l1
(bs1, bs2) = BS.splitAt l1 bs
x1 = bytestringToIntegerBE bs1
x2 = bytestringToIntegerBE bs2
bytestringToIntegerLE :: BS.ByteString -> Integer
bytestringToIntegerLE bs
| l == 0 = 0
| l == 1 = toInteger (BS.head bs)
| otherwise = x2 `B.shiftL` (l1 * 8) B..|. x1
where
l = BS.length bs
l1 = l `div` 2
(bs1, bs2) = BS.splitAt l1 bs
x1 = bytestringToIntegerLE bs1
x2 = bytestringToIntegerLE bs2
bytestringBE :: BS.ByteString -> Pair NatRepr BV
bytestringBE bs = case mkNatRepr (8*fromIntegral (BS.length bs)) of
Some w -> checkNatRepr w $ Pair w (BV (bytestringToIntegerBE bs))
bytestringLE :: BS.ByteString -> Pair NatRepr BV
bytestringLE bs = case mkNatRepr (8*fromIntegral (BS.length bs)) of
Some w -> checkNatRepr w $ Pair w (BV (bytestringToIntegerLE bs))
bytesBE :: [Word8] -> Pair NatRepr BV
bytesBE = bytestringBE . BS.pack
bytesLE :: [Word8] -> Pair NatRepr BV
bytesLE = bytestringLE . BS.pack
asUnsigned :: BV w -> Integer
asUnsigned (BV x) = x
asSigned :: (1 <= w) => NatRepr w -> BV w -> Integer
asSigned w (BV x) =
let wInt = fromNatural (natValue w) in
if B.testBit x (wInt - 1)
then x - B.bit wInt
else x
asNatural :: BV w -> Natural
asNatural = (fromInteger :: Integer -> Natural) . asUnsigned
asBitsBE :: NatRepr w -> BV w -> [Bool]
asBitsBE w bv = [ testBit' i bv | i <- fromInteger <$> [wi - 1, wi - 2 .. 0] ]
where wi = intValue w
asBitsLE :: NatRepr w -> BV w -> [Bool]
asBitsLE w bv = [ testBit' i bv | i <- fromInteger <$> [0 .. wi - 1] ]
where wi = intValue w
integerToBytesBE :: Natural
-> Integer
-> [Word8]
integerToBytesBE n x =
[ fromIntegral (x `B.shiftR` (8*ix)) | ix <- [ni-1, ni-2 .. 0] ]
where ni = fromIntegral n
integerToBytesLE :: Natural
-> Integer
-> [Word8]
integerToBytesLE n x =
[ fromIntegral (x `B.shiftR` (8*ix)) | ix <- [0 .. ni-1] ]
where ni = fromIntegral n
asBytesBE :: NatRepr w -> BV w -> Maybe [Word8]
asBytesBE w (BV x)
| natValue w `mod` 8 == 0 = Just $ integerToBytesBE (natValue w `div` 8) x
| otherwise = Nothing
asBytesLE :: NatRepr w -> BV w -> Maybe [Word8]
asBytesLE w (BV x)
| natValue w `mod` 8 == 0 = Just $ integerToBytesLE (natValue w `div` 8) x
| otherwise = Nothing
asBytestringBE :: NatRepr w -> BV w -> Maybe BS.ByteString
asBytestringBE w bv = BS.pack <$> asBytesBE w bv
asBytestringLE :: NatRepr w -> BV w -> Maybe BS.ByteString
asBytestringLE w bv = BS.pack <$> asBytesLE w bv
and :: BV w -> BV w -> BV w
and (BV x) (BV y) = BV (x B..&. y)
or :: BV w -> BV w -> BV w
or (BV x) (BV y) = BV (x B..|. y)
xor :: BV w -> BV w -> BV w
xor (BV x) (BV y) = BV (x `B.xor` y)
complement :: NatRepr w -> BV w -> BV w
complement w (BV x) = mkBV' w (B.complement x)
shiftAmount :: NatRepr w -> Natural -> Int
shiftAmount w shf = fromNatural (min (natValue w) shf)
shl :: NatRepr w -> BV w -> Natural -> BV w
shl w (BV x) shf = mkBV' w (x `B.shiftL` shiftAmount w shf)
ashr :: (1 <= w) => NatRepr w -> BV w -> Natural -> BV w
ashr w bv shf = mkBV' w (asSigned w bv `B.shiftR` shiftAmount w shf)
lshr :: NatRepr w -> BV w -> Natural -> BV w
lshr w (BV x) shf =
BV (x `B.shiftR` shiftAmount w shf)
rotateL :: NatRepr w -> BV w -> Natural -> BV w
rotateL w bv rot' = leftChunk `or` rightChunk
where rot = if wNatural == 0 then 0 else rot' `mod` wNatural
leftChunk = shl w bv rot
rightChunk = lshr w bv (wNatural - rot)
wNatural = natValue w
rotateR :: NatRepr w -> BV w -> Natural -> BV w
rotateR w bv rot' = leftChunk `or` rightChunk
where rot = if wNatural == 0 then 0 else rot' `mod` wNatural
rightChunk = lshr w bv rot
leftChunk = shl w bv (wNatural - rot)
wNatural = natValue w
bit :: ix+1 <= w
=> NatRepr w
-> NatRepr ix
-> BV w
bit w ix =
checkNatRepr w $
BV (B.bit (fromNatural (natValue ix)))
bit' :: NatRepr w
-> Natural
-> BV w
bit' w ix
| ix < natValue w = checkNatRepr w $ mkBV' w (B.bit (fromNatural ix))
| otherwise = zero w
setBit :: ix+1 <= w
=> NatRepr ix
-> BV w
-> BV w
setBit ix bv =
or bv (BV (B.bit (fromNatural (natValue ix))))
setBit' :: NatRepr w
-> Natural
-> BV w
-> BV w
setBit' w ix bv
| ix < natValue w = or bv (BV (B.bit (fromNatural ix)))
| otherwise = bv
clearBit :: ix+1 <= w
=> NatRepr w
-> NatRepr ix
-> BV w
-> BV w
clearBit w ix bv =
and bv (complement w (BV (B.bit (fromNatural (natValue ix)))))
clearBit' :: NatRepr w
-> Natural
-> BV w
-> BV w
clearBit' w ix bv
| ix < natValue w = and bv (complement w (BV (B.bit (fromNatural ix))))
| otherwise = bv
complementBit :: ix+1 <= w
=> NatRepr ix
-> BV w
-> BV w
complementBit ix bv =
xor bv (BV (B.bit (fromNatural (natValue ix))))
complementBit' :: NatRepr w
-> Natural
-> BV w
-> BV w
complementBit' w ix bv
| ix < natValue w = xor bv (BV (B.bit (fromNatural ix)))
| otherwise = bv
testBit :: ix+1 <= w => NatRepr ix -> BV w -> Bool
testBit ix (BV x) = B.testBit x (fromNatural (natValue ix))
testBit' :: Natural -> BV w -> Bool
testBit' ix (BV x)
| ix > fromIntegral (maxBound :: Int) = False
| otherwise = B.testBit x (fromNatural ix)
popCount :: BV w -> BV w
popCount (BV x) = BV (toInteger (B.popCount x))
ctz :: NatRepr w -> BV w -> BV w
ctz w (BV x) = BV (go 0)
where go !i | i < intValue w &&
B.testBit x (fromInteger i) == False = go (i+1)
| otherwise = i
clz :: NatRepr w -> BV w -> BV w
clz w (BV x) = BV (go 0)
where go !i | i < intValue w &&
B.testBit x (fromInteger (intValue w - i - 1)) == False =
go (i+1)
| otherwise = i
truncBits :: Natural -> BV w -> BV w
truncBits b (BV x) = checkNatural b $ BV (x B..&. (B.bit (fromNatural b) - 1))
add :: NatRepr w -> BV w -> BV w -> BV w
add w (BV x) (BV y) = mkBV' w (x+y)
sub :: NatRepr w -> BV w -> BV w -> BV w
sub w (BV x) (BV y) = mkBV' w (x-y)
mul :: NatRepr w -> BV w -> BV w -> BV w
mul w (BV x) (BV y) = mkBV' w (x*y)
uquot :: BV w -> BV w -> BV w
uquot (BV x) (BV y) = BV (x `quot` y)
urem :: BV w -> BV w -> BV w
urem (BV x) (BV y) = BV (x `rem` y)
uquotRem :: BV w -> BV w -> (BV w, BV w)
uquotRem bv1 bv2 = (uquot bv1 bv2, urem bv1 bv2)
squot :: (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
squot w bv1 bv2 = mkBV' w (x `quot` y)
where x = asSigned w bv1
y = asSigned w bv2
srem :: (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
srem w bv1 bv2 = mkBV' w (x `rem` y)
where x = asSigned w bv1
y = asSigned w bv2
squotRem :: (1 <= w) => NatRepr w -> BV w -> BV w -> (BV w, BV w)
squotRem w bv1 bv2 = (squot w bv1 bv2, srem w bv1 bv2)
sdiv :: (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
sdiv w bv1 bv2 = mkBV' w (x `div` y)
where x = asSigned w bv1
y = asSigned w bv2
smod :: (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
smod w bv1 bv2 = mkBV' w (x `mod` y)
where x = asSigned w bv1
y = asSigned w bv2
sdivMod :: (1 <= w) => NatRepr w -> BV w -> BV w -> (BV w, BV w)
sdivMod w bv1 bv2 = (sdiv w bv1 bv2, smod w bv1 bv2)
abs :: (1 <= w) => NatRepr w -> BV w -> BV w
abs w bv = mkBV' w (Prelude.abs (asSigned w bv))
negate :: NatRepr w -> BV w -> BV w
negate w (BV x) = mkBV' w (-x)
signBit :: 1 <= w => NatRepr w -> BV w -> BV w
signBit w bv@(BV _) = lshr w bv (natValue w - 1) `and` BV 1
signum :: 1 <= w => NatRepr w -> BV w -> BV w
signum w bv = mkBV' w (Prelude.signum (asSigned w bv))
slt :: (1 <= w) => NatRepr w -> BV w -> BV w -> Bool
slt w bv1 bv2 = asSigned w bv1 < asSigned w bv2
sle :: (1 <= w) => NatRepr w -> BV w -> BV w -> Bool
sle w bv1 bv2 = asSigned w bv1 <= asSigned w bv2
ult :: BV w -> BV w -> Bool
ult bv1 bv2 = asUnsigned bv1 < asUnsigned bv2
ule :: BV w -> BV w -> Bool
ule bv1 bv2 = asUnsigned bv1 <= asUnsigned bv2
umin :: BV w -> BV w -> BV w
umin (BV x) (BV y) = if x < y then BV x else BV y
umax :: BV w -> BV w -> BV w
umax (BV x) (BV y) = if x < y then BV y else BV x
smin :: (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
smin w bv1 bv2 = if asSigned w bv1 < asSigned w bv2 then bv1 else bv2
smax :: (1 <= w) => NatRepr w -> BV w -> BV w -> BV w
smax w bv1 bv2 = if asSigned w bv1 < asSigned w bv2 then bv2 else bv1
concat :: NatRepr w
-> NatRepr w'
-> BV w
-> BV w'
-> BV (w+w')
concat w w' (BV hi) (BV lo) = checkNatRepr (w `addNat` w') $
BV ((hi `B.shiftL` (fromNatural (natValue w'))) B..|. lo)
select :: ix + w' <= w
=> NatRepr ix
-> NatRepr w'
-> BV w
-> BV w'
select ix w' (BV x) = mkBV' w' xShf
where xShf = x `B.shiftR` (fromNatural (natValue ix))
select' :: Natural
-> NatRepr w'
-> BV w
-> BV w'
select' ix w' (BV x)
| toInteger ix < toInteger (maxBound :: Int) = mkBV w' (x `B.shiftR` (fromNatural ix))
| otherwise = zero w'
zext :: w + 1 <= w'
=> NatRepr w'
-> BV w
-> BV w'
zext w (BV x) = checkNatRepr w $ BV x
sext :: (1 <= w, w + 1 <= w')
=> NatRepr w
-> NatRepr w'
-> BV w
-> BV w'
sext w w' bv = mkBV w' (asSigned w bv)
trunc :: w' + 1 <= w
=> NatRepr w'
-> BV w
-> BV w'
trunc w' (BV x) = mkBV' w' x
trunc' :: NatRepr w'
-> BV w
-> BV w'
trunc' w' (BV x) = mkBV w' x
mulWide :: NatRepr w -> NatRepr w' -> BV w -> BV w' -> BV (w+w')
mulWide w w' (BV x) (BV y) = checkNatRepr (w `addNat` w') $ BV (x*y)
succUnsigned :: NatRepr w -> BV w -> Maybe (BV w)
succUnsigned w (BV x) =
if x == P.maxUnsigned w
then Nothing
else Just (BV (x+1))
succSigned :: 1 <= w => NatRepr w -> BV w -> Maybe (BV w)
succSigned w (BV x) =
if x == P.maxSigned w
then Nothing
else Just (mkBV' w (x+1))
predUnsigned :: NatRepr w -> BV w -> Maybe (BV w)
predUnsigned w (BV x) =
if x == P.minUnsigned w
then Nothing
else Just (BV (x-1))
predSigned :: 1 <= w => NatRepr w -> BV w -> Maybe (BV w)
predSigned w bv@(BV x) =
if bv == minSigned w
then Nothing
else Just (mkBV' w (x-1))
enumFromToUnsigned :: BV w
-> BV w
-> [BV w]
enumFromToUnsigned bv1 bv2 = BV <$> [asUnsigned bv1 .. asUnsigned bv2]
enumFromToSigned :: 1 <= w => NatRepr w
-> BV w
-> BV w
-> [BV w]
enumFromToSigned w bv1 bv2 = (BV . fromJust . signedToUnsigned w) <$> [asSigned w bv1 .. asSigned w bv2]
ppHex :: NatRepr w -> BV w -> String
ppHex w (BV x) = "0x" ++ N.showHex x "" ++ ":" ++ ppWidth w
ppBin :: NatRepr w -> BV w -> String
ppBin w (BV x) = "0b" ++ N.showIntAtBase 2 intToDigit x "" ++ ":" ++ ppWidth w
ppOct :: NatRepr w -> BV w -> String
ppOct w (BV x) = "0o" ++ N.showOct x "" ++ ":" ++ ppWidth w
ppDec :: NatRepr w -> BV w -> String
ppDec w (BV x) = show x ++ ":" ++ ppWidth w
ppWidth :: NatRepr w -> String
ppWidth w = "[" ++ show (natValue w) ++ "]"