Skip to content
Snippets Groups Projects
Commit 97ec37cc authored by Sebastian Graf's avatar Sebastian Graf Committed by Marge Bot
Browse files

Add regression test for #6070

Fixes #6070.
parent 48bf364e
No related branches found
No related tags found
No related merge requests found
module T6070 where
import qualified Data.Map as M
-- Should unbox `x`, so signature 1!P(..,..)
h :: (Int, Int) -> Int -> (Int, Int)
h x y = if y > 10
then x
else h (case h x 0 of (y1, y2) -> (y2, y1)) (y + 1)
-- Should unbox `(a,b)`, so signature 1!P(..,..)
c :: M.Map Int Int -> (Int, Int)
c m = M.foldrWithKey (\k v (a, b) -> if k + v > 2 then (a, b) else (b, a)) (0, 1) m
==================== Strictness signatures ====================
T6070.c: <1L>
T6070.h: <1!P(L,L)><1!P(L)>
==================== Cpr signatures ====================
T6070.c: 1
T6070.h: 1
==================== Strictness signatures ====================
T6070.c: <1L>
T6070.h: <1!P(L,L)><1!P(L)>
......@@ -18,6 +18,7 @@ test('DmdAnalGADTs', normal, compile, [''])
test('T12370', normal, compile, [''])
test('NewtypeArity', normal, compile, [''])
test('T5075', normal, compile, [''])
test('T6070', normal, compile, [''])
test('T17932', normal, compile, [''])
test('T13380c', expect_broken('!3014'), compile, [''])
test('T13380f', normal, compile, [''])
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment