[GHC] #11179: Allow plugins to access "dead code"
GHC
ghc-devs at haskell.org
Thu Mar 2 18:22:38 UTC 2017
#11179: Allow plugins to access "dead code"
-------------------------------------+-------------------------------------
Reporter: lerkok | Owner: (none)
Type: feature request | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #10823 | Differential Rev(s): Phab:D3073
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by abakst):
Here is one benefit of moving `simpleOptPgm` to a separate pass: I am
currently writing a static analysis as a CoreToCore plugin pass. Consider
the following:
{{{
{-#
OPTIONS_GHC -fplugin Analysis.Plugin
-fplugin-opt Analysis.Plugin:dataNodeProcess
#-}
module DataNode where
import Control.Distributed.Process.ManagedProcess
dataNodeProcess :: ProcessDefinition Int
dataNodeProcess = defaultProcess {
apiHandlers = [handleCall $ \i () -> reply () i]
}
}}}
The associated core *without* optimizations (`ghc -O0 DataNode.hs -ddump-
ds`) is
{{{
dataNodeProcess
dataNodeProcess =
case defaultProcess
of _
{ ProcessDefinition _ ds_d4tk ds_d4tl ds_d4tm ds_d4tn ds_d4to ->
ProcessDefinition
(: ($ (handleCall $dSerializable_a462 $dSerializable_a462)
(\ i_a30r ds_d4tf ->
case ds_d4tf of _ { () -> reply $dSerializable_a462 () i_a30r
}))
[])
ds_d4tk
ds_d4tl
ds_d4tm
ds_d4tn
ds_d4to
}
}}}
The detail isn't important, but since `defaultProcess` is exported
by`ManagedProcess`, the analysis knows what to do. On the other hand, if I
run `ghc -O2 DataNode.hs -ddump-ds`, this is (part of) the resulting core:
{{{
dataNodeProcess
dataNodeProcess =
ProcessDefinition
(build
(\ @ a_d4y4 c_d4y5 n_d4y6 ->
c_d4y5
($ (handleCall $dSerializable_a4an $dSerializable_a4an)
(\ i_a33Z ds_d4y0 ->
case ds_d4y0 of _ { () -> reply $dSerializable_a4an ()
i_a33Z }))
n_d4y6))
[]
[]
(defaultProcess2 `cast` ...)
(defaultProcess1 `cast` ...)
Terminate
}}}
As `defaultProcess1` and `defaultProcess2` are not exported by
`ManagedProcess`, the analysis has no idea what do (which can be quite
annoying if it's in a place where we want precision).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11179#comment:19>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list