`getSizeofMutableByteArray#` may return a negative number

Adithya Kumar adi.obilisetty at gmail.com
Wed Oct 30 12:32:40 UTC 2024


The following test is done with `ghc-9.6.6`.

```
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE MagicHash #-}

import GHC.Base (IO(..))
import GHC.Exts
import Prelude hiding (length)

data MutByteArray = MutByteArray (MutableByteArray# RealWorld)

{-# INLINE new #-}
new :: Int -> IO MutByteArray
new (I# nbytes) = IO $ \s ->
    case newByteArray# nbytes s of
        (# s', mbarr# #) ->
           let c = MutByteArray mbarr#
            in (# s', c #)

{-# INLINE length #-}
length :: MutByteArray -> IO Int
length (MutByteArray arr) =
    IO $ \s ->
        case getSizeofMutableByteArray# arr s of
            (# s1, i #) -> (# s1, I# i #)

test1 :: IO ()
test1 = do
    val <- new (-7)
    len <- length val
    print len

test2 :: IO ()
test2 = do
    val <- new (-8)
    len <- length val
    print len
```

`test1` succeeds and prints `-7`
The test prints the length for all `>= -7`

`test2` fails with `Out of memory`
If `length <= -8`, the test fails with `Out of memory`

This is an interesting quirk.

I expected `newByteArray#` to fail if the size given to it is `< 0` and I
never
expected `getSizeofMutableByteArray#` would return a negative number.

Best,
Adithya
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20241030/40d2fa88/attachment.html>


More information about the ghc-devs mailing list