[GHC] #13536: Program which terminates instantly in GHC 8.0.2 runs for minutes with 8.2.1
GHC
ghc-devs at haskell.org
Thu Apr 6 16:34:10 UTC 2017
#13536: Program which terminates instantly in GHC 8.0.2 runs for minutes 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 rwbarton):
Here is a version without any of the random or quickcheck stuff. (I used
the actual `i`, `b`, `v` values from the test and wrote down an arbitrary
strict function `f`.)
{{{#!hs
{-# LANGUAGE TypeFamilies #-}
module Main where
import Control.Monad (ap, liftM, liftM2, liftM3, replicateM)
import Data.Int (Int32)
main :: IO ()
main = do
let f :: (Bool, Bool) -> (Bool, Bool) -> (Bool, Bool)
f (True, False) (False, False) = (False, True)
f _ _ = (True, False)
((i, b), v) =
((False,True),[(False,True),(False,False),(True,True),(True,False),(False,False),(False,True),(True,True),(True,True),(False,True),(True,False),(False,False),(True,True),(True,True),(False,False),(False,False),(False,True),(True,False),(True,False),(True,True),(True,True),(False,True),(True,False),(True,False),(True,True),(False,False),(True,True),(False,False),(True,False),(False,True),(True,True)])
print $ foldlTest f (i, b) v
type FoldlTest a = (a -> a -> a) -> a -> [a] -> Bool
foldlTest :: FoldlTest (Bool, Bool)
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 Bool where
type Model Bool = Bool
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)
}}}
Observations so far:
* Making the match in `unmodel` lazy (`unmodel ~(a,b) = ...`) makes the
program fast again.
* Adding an explicit export list `module Main (main) where` also makes the
program fast again.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13536#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list