[GHC] #9380: ghc generates seemingly incorrect code

GHC ghc-devs at haskell.org
Thu Jul 31 13:51:35 UTC 2014


#9380: ghc generates seemingly incorrect code
-------------------------------------+-------------------------------------
              Reporter:  qnikst      |            Owner:
                  Type:  bug         |           Status:  closed
              Priority:  normal      |        Milestone:
             Component:  Compiler    |          Version:  7.8.3
            Resolution:  fixed       |         Keywords:
      Operating System:              |     Architecture:  Unknown/Multiple
  Unknown/Multiple                   |       Difficulty:  Unknown
       Type of failure:  Incorrect   |       Blocked By:
  result at runtime                  |  Related Tickets:
             Test Case:  gadt/T9380  |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------

Comment (by maxtaldykin):

 Here is a bit more concise test case (derived from the original one):

 {{{
 {-# LANGUAGE GADTs, DataKinds, KindSignatures #-}

 import Unsafe.Coerce

 data X = A | B
 data Y (x :: X) where
   YA   :: Y A
   YB   :: Y B
   Yany :: String -> Y x

 view :: Y a -> Y b
 view = unsafeCoerce

 main :: IO ()
 main = case view YA of
   YA     -> putStrLn "YA"
   YB     -> putStrLn "YB"
   Yany x -> putStrLn x
 }}}

 This will cause segmentation fault on 7.8.3 due to matching `YA` with
 `Yany` and trying to access `String` that does not exist.

 In HEAD it will print `YA`. But is it really intended behavior?

 My reasoning is that this is an example of unsafe using of `unsafeCoerce`.
 Due to `view`'s parametricity GHC can infer that all valid implementations
 (except _|_) are of the form
 {{{
 view :: Y a -> Y b
 view = const (Yany "some string here")
 }}}

 And it is safe to optimize `main` by dropping `YA` and `YB` cases.

 But if we allow such usage of `unsafeCoerce` then it is no longer possible
 to optimize cases even if `view` absolutely safe.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9380#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list