[GHC] #12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS

#12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider this bare-bones module {{{#!hs {-# OPTIONS -fplugin GHC.TypeLits.Normalise #-} module A where }}} compiling it will always say {{{ $ ghc --make A.hs [1 of 1] Compiling A ( A.hs, A.o ) [GHC.TypeLits.Normalise changed] }}} even when the module was compiled before. {{{ $ ghc A.hs -c -ddump-if-trace -ddump-hi-diffs }}} will give the reason: {{{ imported module ‘GHC.TypeLits.Normalise’ is from package ‘ghc-typelits- natnormalise-0.5’, which is not among previous dependencies }}} Which is the probable cause: when writing the `.hi` file, the used plugins' package dependencies should be also written out. AFAICS they are extracted fron the `DynFlags` but for this comparison in {{{ checkDependencies :: HscEnv -> ModSummary -> ModIface -> IfG RecompileRequired }}} but not found in the `ModSummary` that was originally written to disk. This is pretty nasty for `clash` compilations and the suspected bug is documented here: https://github.com/clash-lang/ghc-typelits- natnormalise/issues/2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12567 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by heisenbug): Following patch seems to fix the problem: {{{#!diff diff --git a/compiler/iface/MkIface.hs b/compiler/iface/MkIface.hs index 8115583..f6856ae 100644 --- a/compiler/iface/MkIface.hs +++ b/compiler/iface/MkIface.hs @@ -1112,6 +1112,12 @@ checkDependencies hsc_env summary iface return (RecompBecause reason) else return UpToDate + | moduleName mod `elem` pluginModNames (hsc_dflags hsc_env) + -> do traceHiDiffs $ + text "imported module " <> quotes (ppr mod) <> + text " is from package " <> quotes (ppr pkg) <> + text ", and is a plugin" + return UpToDate | otherwise -> if pkg `notElem` (map fst prev_dep_pkgs) then do traceHiDiffs $ }}} Of course I am playing fast and loose with other checks. I should e.g. make sure that it is not regularly found first. Anyway, can somebody review this, so that I know I am going in the right general direction? For example as suggested above, the plugin modules' packages could be saved into the `.hi` files. But I did not find a way to do that, as the DynFlags don't track the packages of plugins, only their `ModuleName`s. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12567#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by heisenbug): * failure: None/Unknown => Compile-time performance bug -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12567#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): If a fix for this this could be considered for 8.0.2 it would seriously improve the user experience for compiler plugins greatly! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12567#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS
-------------------------------------+-------------------------------------
Reporter: heisenbug | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Gabor Greif

#12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by heisenbug): When this issue is fixed 18057549ffebea244d9170377889d096ca9fdbcd can be simply reverted. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12567#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): So, there's actually a deeper set of bugs here. See also #7414 and #7277. It would be nice if we could get our hands on an implementation hash; then we can just record it in the interface file directly as a plugin hash and fix things more properly. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12567#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by _deepfire): As a person that suffers a lot from this -- what can be done? What is the "next" step? How much competence is required to debug this? How can a relatively clueless person (like me) help? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12567#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: plugin, | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => plugin, RecompilationCheck -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12567#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: plugin, | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by augustss): Any chance we can get a fix for this? It really, really hurts. At a minimum, give us a flag to ignore plugin dependencies. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12567#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: plugin, | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #7414 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * cc: osa1 (added) * related: => #7414 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12567#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: plugin, | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #7414 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I wrote a proposal which would resolve this issue. https://github.com/ghc-proposals/ghc-proposals/pull/108 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12567#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS
-------------------------------------+-------------------------------------
Reporter: heisenbug | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.3
Resolution: | Keywords: plugin,
| RecompilationCheck
Operating System: Unknown/Multiple | Architecture:
Type of failure: Compile-time | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: #7414 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#12567: `ghc --make` recompiles unchanged files when using `-fplugin` OPTIONS -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: plugin, | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #7414 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.6.1 Comment: Yay, this is fixed! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12567#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC