[commit: ghc] wip/rwbarton-biniface: Boundary condition fixes for Binary (179eafe)

git at git.haskell.org git at git.haskell.org
Mon Feb 20 05:30:48 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/rwbarton-biniface
Link       : http://ghc.haskell.org/trac/ghc/changeset/179eafedda7c2063c07858b79d32b7d90e32cb0b/ghc

>---------------------------------------------------------------

commit 179eafedda7c2063c07858b79d32b7d90e32cb0b
Author: Reid Barton <rwbarton at gmail.com>
Date:   Sun Feb 19 20:06:13 2017 -0500

    Boundary condition fixes for Binary


>---------------------------------------------------------------

179eafedda7c2063c07858b79d32b7d90e32cb0b
 compiler/utils/Binary.hs | 8 +++++---
 1 file changed, 5 insertions(+), 3 deletions(-)

diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs
index a1ccee3..4398f12 100644
--- a/compiler/utils/Binary.hs
+++ b/compiler/utils/Binary.hs
@@ -101,6 +101,7 @@ data BinHandle
   = BinMem {                     -- binary data stored in an unboxed array
      bh_usr :: UserData,         -- sigh, need parameterized modules :-)
      _off_r :: !FastMutInt,      -- the current offset
+                                 -- Invariant: _off_r <= _sz_r
      _sz_r  :: !FastMutInt,      -- size of the array (cached)
      _arr_r :: !(IORef BinArray) -- the array (bounds: (0,size-1))
     }
@@ -174,7 +175,7 @@ tellBin (BinMem _ r _ _) = do ix <- readFastMutInt r; return (BinPtr ix)
 seekBin :: BinHandle -> Bin a -> IO ()
 seekBin h@(BinMem _ ix_r sz_r _) (BinPtr p) = do
   sz <- readFastMutInt sz_r
-  if (p >= sz)
+  if (p > sz)
         then do expandBin h p; writeFastMutInt ix_r p
         else writeFastMutInt ix_r p
 
@@ -183,7 +184,7 @@ seekBy h@(BinMem _ ix_r sz_r _) off = do
   sz <- readFastMutInt sz_r
   ix <- readFastMutInt ix_r
   let ix' = ix + off
-  if (ix' >= sz)
+  if (ix' > sz)
         then do expandBin h ix'; writeFastMutInt ix_r ix'
         else writeFastMutInt ix_r ix'
 
@@ -219,7 +220,8 @@ readBinMem filename = do
   writeFastMutInt sz_r filesize
   return (BinMem noUserData ix_r sz_r arr_r)
 
--- expand the size of the array to include a specified offset
+-- expand the size of the array to strictly include a specified offset
+-- (i.e., not at EOF, so we can write at least one byte there)
 expandBin :: BinHandle -> Int -> IO ()
 expandBin (BinMem _ _ sz_r arr_r) off = do
    sz <- readFastMutInt sz_r



More information about the ghc-commits mailing list