Skip to content

Commit

Permalink
Fix overflow bug in shiftByteString, add tests to ensure it stays fixed
Browse files Browse the repository at this point in the history
  • Loading branch information
kozross committed Jul 17, 2024
1 parent 0c02489 commit 6203592
Show file tree
Hide file tree
Showing 3 changed files with 20 additions and 4 deletions.
3 changes: 3 additions & 0 deletions plutus-core/plutus-core/src/PlutusCore/Bitwise.hs
Original file line number Diff line number Diff line change
Expand Up @@ -656,6 +656,9 @@ shiftByteString :: ByteString -> Int -> ByteString
shiftByteString bs bitMove
| BS.null bs = bs
| bitMove == 0 = bs
-- Needed to guard against overflow when given minBound for Int as a bit move
| abs (fromIntegral bitMove) >= (fromIntegral bitLen :: Integer) =
BS.replicate len 0x00
| otherwise = unsafeDupablePerformIO . BS.useAsCString bs $ \srcPtr ->
BSI.create len $ \dstPtr -> do
-- To simplify our calculations, we work only with absolute values,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}

-- | Tests for [this
-- CIP](https://github.com/mlabs-haskell/CIPs/blob/koz/bitwise/CIP-XXXX/CIP-XXXX.md)
-- | Tests for [CIP-123](https://github.com/cardano-foundation/CIPs/tree/master/CIP-0123)
module Evaluation.Builtins.Bitwise (
shiftHomomorphism,
rotateHomomorphism,
Expand All @@ -21,7 +20,8 @@ module Evaluation.Builtins.Bitwise (
ffsReplicate,
ffsXor,
ffsIndex,
ffsZero
ffsZero,
shiftMinBound
) where

import Control.Monad (unless)
Expand All @@ -38,6 +38,17 @@ import Test.Tasty (TestTree)
import Test.Tasty.Hedgehog (testPropertyNamed)
import Test.Tasty.HUnit (testCase)

-- | If given 'Int' 'minBound' as an argument, shifts behave sensibly.
shiftMinBound :: Property
shiftMinBound = property $ do
bs <- forAllByteString 0 512
let len = BS.length bs
let shiftExp = mkIterAppNoAnn (builtin () PLC.ShiftByteString) [
mkConstant @ByteString () bs,
mkConstant @Integer () . fromIntegral $ (minBound :: Int)
]
evaluatesToConstant @ByteString (BS.replicate len 0x00) shiftExp

-- | Finding the first set bit in a bytestring with only zero bytes should always give -1.
ffsZero :: Property
ffsZero = property $ do
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -972,7 +972,9 @@ test_Bitwise =
testPropertyNamed "positive shifts clear low indexes" "shift_pos_low"
Bitwise.shiftPosClearLow,
testPropertyNamed "negative shifts clear high indexes" "shift_neg_high"
Bitwise.shiftNegClearHigh
Bitwise.shiftNegClearHigh,
testPropertyNamed "shifts do not break when given minBound as a shift" "shift_min_bound"
Bitwise.shiftMinBound
],
testGroup "rotateByteString" [
testGroup "homomorphism" Bitwise.rotateHomomorphism,
Expand Down

0 comments on commit 6203592

Please sign in to comment.