[GHC] #14335: Annotations aren't supported with -fexternal-interpreter

GHC ghc-devs at haskell.org
Mon Feb 26 12:43:14 UTC 2018


#14335: Annotations aren't supported with -fexternal-interpreter
-------------------------------------+-------------------------------------
        Reporter:  bgamari           |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:  8.6.1
       Component:  Compiler          |              Version:  8.2.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:  T14335
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by osa1):

 As suggested in comment:2, this doesn't require `ANN`, `-fplugin` simply
 doesn't work with `-fexternal-interpreter`.

 Reproducer:

 {{{
 $ cat plugin/src/Plugin.hs
 module Plugin where

 import GhcPlugins

 plugin :: Plugin
 plugin = defaultPlugin{ installCoreToDos = install }

 install :: [CommandLineOption] -> [CoreToDo] -> CoreM [CoreToDo]
 install _ todo = do
     return (CoreDoPluginPass "test plugin" pass : todo)

 pass :: ModGuts -> CoreM ModGuts
 pass g = return g

 $ cat test.hs
 {-# OPTIONS_GHC -fplugin Plugin #-}

 module Test where

 $ ghc-stage2 test.hs -fforce-recomp -fexternal-interpreter
 [1 of 1] Compiling Test             ( test.hs, test.o )
 getHValueSafely plugin (Plugin)
 CallStack (from HasCallStack):
   wormholeRef, called at compiler/ghci/GHCi.hs:622:21 in ghc:GHCi
   wormhole, called at compiler/main/DynamicLoading.hs:189:56 in
 ghc:DynamicLoading
   getHValueSafely, called at compiler/main/DynamicLoading.hs:161:44 in
 ghc:DynamicLoading
   getValueSafely, called at compiler/main/DynamicLoading.hs:107:24 in
 ghc:DynamicLoading
   loadPlugin', called at compiler/main/DynamicLoading.hs:87:14 in
 ghc:DynamicLoading
 ghc-stage2: this operation requires -fno-external-interpreter
 }}}

 The call stack is added by me to debug. `getHValueSafely` is being called
 to get `plugin :: Plugin` from the plugin module.

 The problem is we're trying to dereference a `HValueRef` returned by the
 external GHCi process. If we want plugins to work with `-fexternal-
 interpreter` I guess we have to let GHCi run the plugin passes and somehow
 return results to `TcRnDriver` (and `SimplCore` for Core plugins). I just
 started reading the relevant code, but I think we may need new GHCi
 messages for these? As parameter we need to pass the whole `TcM` (and
 `CoreM` for Core plugins) context.

 @bgamari @simonmar does this make sense?

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14335#comment:11>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list