[Git][ghc/ghc][master] 2 commits: Add minimal test for #12492

Marge Bot gitlab at gitlab.haskell.org
Tue Jul 28 00:09:51 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
6da73bbf by Michalis Pardalos at 2020-07-27T20:09:44-04:00
Add minimal test for #12492

- - - - -
47680cb7 by Michalis Pardalos at 2020-07-27T20:09:44-04:00
Use allocate, not ALLOC_PRIM_P for unpackClosure#

ALLOC_PRIM_P fails for large closures, by directly using allocate
we can handle closures which are larger than the block size.

Fixes #12492

- - - - -


3 changed files:

- rts/PrimOps.cmm
- + testsuite/tests/primops/should_run/T12492.hs
- testsuite/tests/primops/should_run/all.T


Changes:

=====================================
rts/PrimOps.cmm
=====================================
@@ -2360,6 +2360,7 @@ stg_mkApUpd0zh ( P_ bco )
 stg_unpackClosurezh ( P_ closure )
 {
     W_ info, ptrs, nptrs, p, ptrs_arr, dat_arr;
+    MAYBE_GC_P(stg_unpackClosurezh, closure);
     info  = %GET_STD_INFO(UNTAG(closure));
     prim_read_barrier;
 
@@ -2375,12 +2376,13 @@ stg_unpackClosurezh ( P_ closure )
     (len) = foreign "C" heap_view_closureSize(clos "ptr");
 
     W_ ptrs_arr_sz, ptrs_arr_cards, dat_arr_sz;
-    dat_arr_sz = SIZEOF_StgArrBytes + WDS(len);
-
-    ALLOC_PRIM_P (dat_arr_sz, stg_unpackClosurezh, closure);
-
-    dat_arr = Hp - dat_arr_sz + WDS(1);
 
+    dat_arr_sz = SIZEOF_StgArrBytes + WDS(len);
+    ("ptr" dat_arr) = ccall allocateMightFail(MyCapability() "ptr", BYTES_TO_WDS(dat_arr_sz));
+    if (dat_arr == NULL) (likely: False) {
+        jump stg_raisezh(base_GHCziIOziException_heapOverflow_closure);
+    }
+    TICK_ALLOC_PRIM(SIZEOF_StgArrBytes, WDS(len), 0);
 
     SET_HDR(dat_arr, stg_ARR_WORDS_info, CCCS);
     StgArrBytes_bytes(dat_arr) = WDS(len);


=====================================
testsuite/tests/primops/should_run/T12492.hs
=====================================
@@ -0,0 +1,11 @@
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+
+import GHC.Exts
+import GHC.IO
+
+main :: IO ()
+main = IO $ \s -> case newByteArray# 1032161# s of
+  (# s', mba# #) -> case unpackClosure# (unsafeCoerce# mba# :: Any) of
+    (# !_, _, _ #) -> (# s', () #)


=====================================
testsuite/tests/primops/should_run/all.T
=====================================
@@ -19,6 +19,7 @@ test('ArithWord8', omit_ways(['ghci']), compile_and_run, [''])
 test('CmpInt8', normal, compile_and_run, [''])
 test('CmpWord8', normal, compile_and_run, [''])
 test('ShowPrim', normal, compile_and_run, [''])
+test('T12492', normal, compile_and_run, [''])
 
 # These two tests use unboxed tuples, which GHCi doesn't support
 test('ArithInt16', omit_ways(['ghci']), compile_and_run, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aa054d32a8ff69c334293a0d6c9d11b83a236a96...47680cb76b068508fd16d052e0a3bed12e38ea5f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aa054d32a8ff69c334293a0d6c9d11b83a236a96...47680cb76b068508fd16d052e0a3bed12e38ea5f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200727/6f95f5c1/attachment-0001.html>


More information about the ghc-commits mailing list