
#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 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): More progress. Here is a program which //deterministically// exhibits the issue (i.e., it doesn't rely on system-generated pseudorandomness): {{{#!hs {-# LANGUAGE TypeFamilies #-} module Main (main) where import System.Random.TF.Gen (seedTFGen) import Test.QuickCheck (arbitrary) import Test.QuickCheck.Gen (Gen(..)) import Test.QuickCheck.Random (QCGen(..)) import Text.Show.Functions () main :: IO () main = do let tfGen = seedTFGen ( 543863073959529591 , 14453565003432405558 , 3036645681517334938 , 17781306407512891751 ) qcGen = QCGen tfGen (f, (i, b), v) = case arbitrary of MkGen g -> g qcGen 30 print $ foldlTest f (i, b) v type FoldlTest a = (a -> a -> a) -> a -> [a] -> Bool foldlTest :: FoldlTest (Int, Int) foldlTest f (i, b) v = foldl f (i, b) v == foldl (\x -> f (unmodel x)) (i, b) v class TestData a where type Model a unmodel :: Model a -> a 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) }}} I'd also like to retract my claim that this program is looping forever. I timed this program when compiled with `-O2` on GHC 8.2.1: {{{ 137.01user 0.47system 2:17.43elapsed 100%CPU (0avgtext+0avgdata 7476maxresident)k 0inputs+0outputs (0major+936minor)pagefaults 0swaps }}} As opposed to GHC 8.0.2: {{{ 0.00user 0.00system 0:00.00elapsed 0%CPU (0avgtext+0avgdata 4768maxresident)k 0inputs+0outputs (0major+289minor)pagefaults 0swaps }}} So there's still a bug, but I don't think it's infinite in nature. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13536#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler