[GHC] #16208: map/coerce does not fire with all newtypes
GHC
ghc-devs at haskell.org
Mon Jan 21 16:10:22 UTC 2019
#16208: map/coerce does not fire with all newtypes
-------------------------------------+-------------------------------------
Reporter: monoidal | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.6.3
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Consider a slightly modified version of T2110, compiled with -O:
{{{
#!haskell
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE RankNTypes #-}
import GHC.Exts
import Unsafe.Coerce
newtype Age a b where
Age :: forall a b. Int -> Age a b
foo :: [Int] -> [Int]
foo = map id
fooAge :: [Int] -> [Age a b]
fooAge = map Age
fooCoerce :: [Int] -> [Age a b]
fooCoerce = map coerce
fooUnsafeCoerce :: [Int] -> [Age a b]
fooUnsafeCoerce = map unsafeCoerce
same :: a -> b -> IO ()
same x y = case reallyUnsafePtrEquality# (unsafeCoerce x) y of
1# -> putStrLn "yes"
_ -> putStrLn "no"
main = do
let l = [1,2,3]
same (foo l) l
same (fooAge l) l
same (fooCoerce l) l
same (fooUnsafeCoerce l) l
}}}
This code correctly prints "yes" four times, as required by #2110.
However, changing the order of type arguments in the definition of Age to:
{{{
Age :: forall b a. Int -> Age a b
}}}
causes the test to fail in one case: `map Age` is no longer simplified to
`Age`. The reason is that this change causes the newtype `Age` to have a
wrapper, and the map/coerce rule is not detecting it (see Note [Getting
the map/coerce RULE to work] and Note [Data con wrappers and GADT syntax])
This ticket is a prerequisite to linear types (since in linear types, all
newtypes have wrappers).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16208>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list