[commit: ghc] wip/map-coerce-wrappers: Fix map/coerce for newtypes with wrappers (Trac #16208) (44bbf4f)

git at git.haskell.org git at git.haskell.org
Sat Feb 16 10:33:16 UTC 2019


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/map-coerce-wrappers
Link       : http://ghc.haskell.org/trac/ghc/changeset/44bbf4f4fac5f53ebb5c167f80c75c5fa420fcb1/ghc

>---------------------------------------------------------------

commit 44bbf4f4fac5f53ebb5c167f80c75c5fa420fcb1
Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io>
Date:   Fri Feb 15 15:58:15 2019 +0100

    Fix map/coerce for newtypes with wrappers (Trac #16208)


>---------------------------------------------------------------

44bbf4f4fac5f53ebb5c167f80c75c5fa420fcb1
 compiler/coreSyn/CoreOpt.hs                           | 19 +++++++++++++++++++
 .../simplCore/should_run/{T2110.hs => T16208.hs}      | 11 +++++++----
 .../should_run/{T2110.stdout => T16208.stdout}        |  0
 testsuite/tests/simplCore/should_run/all.T            |  1 +
 4 files changed, 27 insertions(+), 4 deletions(-)

diff --git a/compiler/coreSyn/CoreOpt.hs b/compiler/coreSyn/CoreOpt.hs
index 29f8ab2..8ffc58c 100644
--- a/compiler/coreSyn/CoreOpt.hs
+++ b/compiler/coreSyn/CoreOpt.hs
@@ -291,6 +291,12 @@ simple_app env (Var v) as
     -- See Note [Unfold compulsory unfoldings in LHSs]
   = simple_app (soeZapSubst env) (unfoldingTemplate unf) as
 
+  | let unf = idUnfolding v
+  , Just a <- isDataConWrapId_maybe v
+  , isNewTyCon (dataConTyCon a)
+    -- See note [Unfold newtype wrappers in LHSs]
+  = simple_app (soeZapSubst env) (unfoldingTemplate unf) as
+
   | otherwise
   , let out_fn = lookupIdSubst (text "simple_app") (soe_subst env) v
   = finish_app env out_fn as
@@ -582,6 +588,19 @@ However, we don't want to inline 'seq', which happens to also have a
 compulsory unfolding, so we only do this unfolding only for things
 that are always-active.  See Note [User-defined RULES for seq] in MkId.
 
+Note [Unfold newtype wrappers in LHSs]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Newtypes may have wrappers, e.g.
+
+newtype Age a b where
+ MkAge :: forall b a. Int -> Age a b
+
+(the wrapper reorders the type arguments)
+
+In order for the `map coerce = coerce` rule to match `map MkAge` (as
+it should!), we need to unfold newtype wrappers in simple_app. See also Note
+[Unfold compulsory unfoldings in LHSs] and Trac #16208.
+
 Note [Getting the map/coerce RULE to work]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 We wish to allow the "map/coerce" RULE to fire:
diff --git a/testsuite/tests/simplCore/should_run/T2110.hs b/testsuite/tests/simplCore/should_run/T16208.hs
similarity index 68%
copy from testsuite/tests/simplCore/should_run/T2110.hs
copy to testsuite/tests/simplCore/should_run/T16208.hs
index d945fac..60c3af7 100644
--- a/testsuite/tests/simplCore/should_run/T2110.hs
+++ b/testsuite/tests/simplCore/should_run/T16208.hs
@@ -1,17 +1,20 @@
+{-# LANGUAGE GADTs #-}
 {-# LANGUAGE MagicHash #-}
+{-# LANGUAGE RankNTypes #-}
 
 import GHC.Exts
 import Unsafe.Coerce
 
-newtype Age = Age Int
+newtype Age a b where
+  Age :: forall b a. Int -> Age a b
 
 foo :: [Int] -> [Int]
 foo = map id
-fooAge :: [Int] -> [Age]
+fooAge :: [Int] -> [Age a b]
 fooAge = map Age
-fooCoerce :: [Int] -> [Age]
+fooCoerce :: [Int] -> [Age a b]
 fooCoerce = map coerce
-fooUnsafeCoerce :: [Int] -> [Age]
+fooUnsafeCoerce :: [Int] -> [Age a b]
 fooUnsafeCoerce = map unsafeCoerce
 
 same :: a -> b -> IO ()
diff --git a/testsuite/tests/simplCore/should_run/T2110.stdout b/testsuite/tests/simplCore/should_run/T16208.stdout
similarity index 100%
copy from testsuite/tests/simplCore/should_run/T2110.stdout
copy to testsuite/tests/simplCore/should_run/T16208.stdout
diff --git a/testsuite/tests/simplCore/should_run/all.T b/testsuite/tests/simplCore/should_run/all.T
index f808943..646929f 100644
--- a/testsuite/tests/simplCore/should_run/all.T
+++ b/testsuite/tests/simplCore/should_run/all.T
@@ -50,6 +50,7 @@ test('T5441', [], multimod_compile_and_run, ['T5441', ''])
 test('T5603', reqlib('integer-gmp'), compile_and_run, [''])
 test('T2110', normal, compile_and_run, [''])
 test('AmapCoerce', normal, compile_and_run, [''])
+test('T16208', normal, compile_and_run, [''])
 
 # Run these tests *without* optimisation too
 test('T5625', [ only_ways(['normal','optasm']), exit_code(1) ], compile_and_run, [''])



More information about the ghc-commits mailing list