[GHC] #4012: Compilation results are not deterministic
GHC
ghc-devs at haskell.org
Fri Apr 17 06:30:51 UTC 2015
#4012: Compilation results are not deterministic
-------------------------------------+-------------------------------------
Reporter: kili | Owner: Fuuzetsu
Type: bug | Status: new
Priority: normal | Milestone: 7.12.1
Component: Compiler | Version: 6.12.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Other | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Fuuzetsu):
Got the below in mail few days ago but I don't have time to investigate
myself for next few weeks. Just putting it out there. Seems like a pretty
big issue.
--
Hi,
trac seems to be down currently so I'm sending this directly to you.
Using GHC 7.10, I reduced the code to this:
{{{
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Test where
import Control.Monad.Trans.Reader
newtype EventM a = EventM { unEventM :: ReaderT () IO a } deriving
(Functor, Applicative, Monad)
}}}
Compiling with:
{{{
ghc -i../.. test.hs -O
ghc --show-iface test.hi > 1.hi
ghc -i../.. test.hs -O -fforce-recomp
ghc --show-iface test.hi > 2.hi
}}}
Now {{{1.hi}}} and {{{2.hi}}} differ, including in their ABI hash. I'm not
sure if
there are any other examples of nondeterminism in this module, since I
continued reducing as long as GHC gave different interface hashes, I did
not check whether the cause was actually the same.
In this case, this seems to be the most significant difference:
{{{
512a513,517
"SPEC/Test $fApplicativeReaderT_$cpure @ () @ IO" [ALWAYS] forall
$dFunctor
:: Functor
(ReaderT () IO)
$dApplicative :: Applicative IO
$fApplicativeReaderT_$cpure @ () @ IO $dFunctor $dApplicative
= $fMonadEventM_$s$fApplicativeReaderT_$cpure
521,525d525
"SPEC/Test $fMonadReaderT_$creturn @ () @ IO" [ALWAYS] forall
$dApplicative :: Applicative
(ReaderT () IO)
$dMonad ::
Monad IO
$fMonadReaderT_$creturn @ () @ IO $dApplicative $dMonad
= $fMonadEventM_$s$fMonadReaderT_$creturn
}}}
If I read this correctly, it means that in one case, a specialization rule
is generated for return, will in the other case, GHC generates one for
pure.
Looking further, there is also the following difference:
{{{
$fMonadEventM_$s$fApplicativeReaderT :: Applicative (ReaderT () IO)
{- HasNoCafRefs, Strictness: m, Inline: [ALWAYS] CONLIKE,
Unfolding: DFun:.
@ (ReaderT () IO)
$fMonadEventM3
$fMonadEventM_$s$fMonadReaderT_$creturn
($fApplicativeReaderT_$c<*>
@ ()
@ IO
$fMonadEventM3
$fApplicativeIO)
$fMonadEventM_$s$fApplicativeReaderT_$c*>
$fMonadEventM_$s$fApplicativeReaderT_$c<* -}
vs
$fMonadEventM_$s$fApplicativeReaderT :: Applicative (ReaderT () IO)
{- HasNoCafRefs, Strictness: m, Inline: [ALWAYS] CONLIKE,
Unfolding: DFun:.
@ (ReaderT () IO)
$fMonadEventM3
$fMonadEventM_$s$fApplicativeReaderT_$cpure
($fApplicativeReaderT_$c<*>
@ ()
@ IO
$fMonadEventM3
$fApplicativeIO)
$fMonadEventM_$s$fApplicativeReaderT_$c*>
$fMonadEventM_$s$fApplicativeReaderT_$c<* -}
}}}
(Notice the pure vs return again)
Regards,
Benno
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/4012#comment:76>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list