[GHC] #14361: GHC HEAD miscompiles `text-containers`

GHC ghc-devs at haskell.org
Tue Oct 17 16:38:15 UTC 2017


#14361: GHC HEAD miscompiles `text-containers`
-------------------------------------+-------------------------------------
        Reporter:  hvr               |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  high              |            Milestone:  8.4.1
       Component:  Compiler          |              Version:  8.3
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Incorrect result  |  Unknown/Multiple
  at runtime                         |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by hvr):

 To make things easier, here's a smaller repro-case which doesn't require
 building the test-suite of `text-containers`:

 {{{#!hs
 {-# LANGUAGE OverloadedLists   #-}
 {-# LANGUAGE OverloadedStrings #-}

 module Main where

 import           Control.Monad
 import qualified Data.List            as List
 import           Data.String
 import qualified Data.TextSet.Unboxed as TS

 main :: IO ()
 main = do
   putStrLn "START"

   forM_ ([ 0 .. 10 ] :: [Int]) $ \_ -> do
     forM_ (zip [ 1::Int .. ] (List.inits testData)) $ \(j,xs) -> do
       unless (all (`TS.member` (TS.fromList xs)) xs) $ putStr (show j ++ "
 ")

     forM_ (zip [ 1::Int .. ] (List.tails testData)) $ \(j,xs) -> do
       unless (all (`TS.member` (TS.fromList xs)) xs) $ putStr (show (-j)
 ++ " ")

   putStrLn ""
   putStrLn "DONE"

   return ()

 testData :: [TS.Key]
 testData = [ fromString [c] | c <- ['A' .. 'Z'] ]
 }}}


 If you have Cabal 2.1+, you can simply use its generated GHC environment
 file via

 {{{
 # solve & build *only* the library component, and generate
 .ghc.environment.* file
 $ cabal new-build lib:text-containers --disable-tests -w ghc-8.3.20171016

 # build test program
 $ ghc-8.3.20171016 --make -Wall -O1  bug-t14361.hs
 [1 of 1] Compiling Main             ( bug-t14361.hs, bug-t14361.o )
 Linking bug-t14361 ...

 # run test program
 $ ./bug-t14361
 START
 22 -2 -23 -3 -1 26 -1 -15 11 12 13 -8 7 15 18 -11 19 -2 -1 26 -1 26 -1
 DONE
 }}}


 If the program was executed correctly the output would have no numbers,
 i.e. it would look like

 {{{
 START

 DONE
 }}}

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


More information about the ghc-tickets mailing list