[GHC] #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails

GHC ghc-devs at haskell.org
Fri Mar 23 07:08:44 UTC 2018


#14965: GHC 8.4.1 bug: -O + separate compilation + three list fields +
concatenation; core-lint fails
-------------------------------------+-------------------------------------
           Reporter:  blynn          |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.4.1
           Keywords:                 |  Operating System:  Linux
       Architecture:                 |   Type of failure:  Incorrect result
  Unknown/Multiple                   |  at runtime
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 A simple program that works in 8.2.1 fails in 8.4.1 when compiled with -O.
 (Sorry, haven't tested 8.2.2.) GHC with -dcore-lint reports an error.

 See attached files. In one file I declared:

 {{{#!hs
 module Sep where

 data Sep = Sep
   { bugVanishesWithoutThis :: [()]
   , middle :: [String]
   , orThis :: [()]
   }

 catSep :: Sep -> Sep -> Sep
 catSep (Sep a b c) (Sep x y z) = Sep (a ++ x) (b ++ y) (c ++ z)

 cc :: Sep -> Bool
 cc boost = elem "foo" $ middle boost
 }}}

 and in a second file, simple code fails when compiled with -O:

 {{{#!hs
 module Main (main) where

 import Sep

 main :: IO ()
 main = print $ cc bb

 bb :: Sep
 bb = catSep b1 b2

 b1 :: Sep
 b1 = Sep [] ["foo"] []

 b2 :: Sep
 b2 = Sep [] ["bar"] []
 }}}

 This should print "True", and does so for GHC 8.2.1, and GHC 8.4.1 without
 -O, but prints "False" for GHC 8.4.1 with -O.

 I was unable to reproduce the bug with a single file.

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


More information about the ghc-tickets mailing list