What does freezing an array really do?

Bertram Felgenhauer bertram.felgenhauer at googlemail.com
Thu Aug 20 22:12:07 UTC 2020


David Feuer wrote:
> I know that a frozen array doesn't have to be searched for elements in
> a younger generation, but how does it differ from an unfrozen array
> that hasn't been mutated since the last collection?

Frozen arrays are not put on the mutable list once they're clean
(meaning they have no references to younger generations). Thawed
arrays are always on the mutable list.

Cheers,

Bertram


You can crash a program by updating a clean frozen array in the old
generation, then doing a minor GC, and then accessing the updated
entry:

import Data.Array
import Data.Array.Base (unsafeFreezeIOArray, unsafeThawIOArray)
import Data.Array.IO
import Data.Array.Unsafe
import System.Mem
import Control.Monad (forM_)

main = do
    arr <- newArray (0, 1024) 42 :: IO (IOArray Int Int)
    -- `arr` points to a MUT_ARR_PTRS closure

    arr' <- unsafeFreezeIOArray arr :: IO (Array Int Int)
    -- unsafeFreezeIOArray changes the closure type to
    -- MUT_ARR_PTRS_FROZEN_DIRTY

    performMajorGC
    -- the first major GC changes it to MUT_ARR_PTRS_FROZEN

    performMajorGC
    -- the second GC kicks it off the mutable list??

    -- unsafeThaw would change the closure type to MUT_ARR_PTRS_DIRTY
    -- *and* put the array on the mutable list.
    -- _ <- unsafeThawIOArray arr'

    -- in contrast, `writeArray` changes the closure type to
    -- MUT_ARR_PTRS_DIRTY but does not touch the `mutable list`
    forM_ [0..1023] $ \i -> do
        writeArray arr i $ f i

    print $ sum [1..1000000]
    -- Evaluating the sum produces a lot of garbage, and the minor GCs
    -- will not scan the array.

    arr' <- unsafeFreezeIOArray arr :: IO (Array Int Int)
    print $ arr' ! 0
    print $ arr' ! 1
    -- so these array entries have a good chance to point to utter garbage.

{-# NOINLINE f #-}
f x = x*x

{-

> ghc -O0 Crash.hs && ./Crash
[1 of 1] Compiling Main             ( Crash.hs, Crash.o )
Linking Crash ...
Crash: internal error: evacuate: strange closure type 29041
    (GHC version 8.6.5 for x86_64_unknown_linux)
    Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
Aborted (core dumped)

> ghc -O1 Crash.hs && ./Crash
[1 of 1] Compiling Main             ( Crash.hs, Crash.o )
Linking Crash ...
500000500000
482299980870
Segmentation fault (core dumped)

> ghc -O2 Crash.hs && ./Crash
[1 of 1] Compiling Main             ( Crash.hs, Crash.o ) [Optimisation flags changed]
Linking Crash ...
500000500000
482299980870
Segmentation fault (core dumped)

-}


More information about the Glasgow-haskell-users mailing list