
#13536: Program which terminated in GHC 8.0.2 loops with 8.2.1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This currently causes the `vector` test suite to loop forever (see [https://github.com/haskell/vector/pull/161#issuecomment-292031845 here]). I've reproduced this with GHC 8.2.1 and HEAD. Unfortunately, it's not easy to isolate down to a file with no dependencies, so for now this requires `vector` and `QuickCheck` to reproduce. First, install them: {{{ $ cabal install vector QuickCheck --allow-newer -w /opt/ghc/8.2.1/bin/ghc }}} Then take this file: {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-} module Main (main) where import qualified Data.Vector.Generic as V import qualified Data.Vector.Unboxed as DVU import Test.QuickCheck import Text.Show.Functions () main :: IO () main = do verboseCheck ((\f (i, b) v -> V.foldl f (i, b) v == foldl (\x -> f (unmodel x)) (i, b) ( DVU.toList v)) :: ((Int, Bool) -> (Int, Bool) -> (Int, Bool)) -> (Int, Bool) -> DVU.Vector (Int, Bool) -> Bool) instance (Arbitrary a, DVU.Unbox a) => Arbitrary (DVU.Vector a) where arbitrary = fmap DVU.fromList arbitrary class TestData a where type Model a unmodel :: Model a -> a instance TestData Bool where type Model Bool = Bool unmodel = id instance TestData Int where type Model Int = Int unmodel = id instance (Eq a, Eq b, TestData a, TestData b) => TestData (a,b) where type Model (a,b) = (Model a, Model b) unmodel (a,b) = (unmodel a, unmodel b) }}} Then compile it with `/opt/ghc/8.2.1/bin/ghc -O2 Main.hs` (the `-O2` part is important). Observe that running it never terminates. However, the same program //does// terminate when compiled with 8.0.2! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13536 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler