`writeCharArray#` behaves different than `writeWord8Array#` under -fcheck-prim-bounds
As discussed on IRC, there seems to be an issue with bounds checking in this code:
instance Read ShortByteString where
readsPrec p str = [ (packChars x, y) | (x, y) <- readsPrec p str ]
instance IsString ShortByteString where
fromString = packChars
packChars :: [Char] -> ShortByteString
packChars cs = packLenChars (List.length cs) cs
packLenChars :: Int -> [Char] -> ShortByteString
packLenChars len cs0 =
create len (\mba -> go mba 0 cs0)
where
go :: MBA s -> Int -> [Char] -> ST s ()
go !_ !_ [] = return ()
go !mba !i (c:cs) = do
writeCharArray mba i c
go mba (i+1) cs
writeCharArray :: MBA s -> Int -> Char -> ST s ()
writeCharArray (MBA# mba#) (I# i#) (C# c#) =
ST $ \s -> case writeCharArray# mba# i# c# s of
s -> (# s, () #)
The documentation of writeCharArray# indicates that it truncates correctly.
The following patch makes the bounds checking error go away:
--- a/Data/ByteString/Short/Internal.hs
+++ b/Data/ByteString/Short/Internal.hs
@@ -442,7 +444,7 @@ packLenChars len cs0 =
go :: MBA s -> Int -> [Char] -> ST s ()
go !_ !_ [] = return ()
go !mba !i (c:cs) = do
- writeCharArray mba i c
+ writeWord8Array mba i (BS.c2w c)
go mba (i+1) cs
There was never any test failure with both methods.
Repro test case:
- clone https://github.com/hasufell/bytestring/tree/bounds-checking-repro
- run
cabal run --ghc-options='-fcheck-prim-bounds -fno-ignore-asserts' bytestring-tests
with the appropriate GHC supporting bounds checking - see it fail
- revert
6511781751228526b81188971c8baf316f3ad8dc
- run the test again