[GHC] #10077: Providing type checker plugin on command line results in false cyclic import error

GHC ghc-devs at haskell.org
Tue Feb 10 10:36:27 UTC 2015


#10077: Providing type checker plugin on command line results in false cyclic
import error
-------------------------------------+-------------------------------------
              Reporter:  jbracker    |             Owner:
                  Type:  bug         |            Status:  new
              Priority:  normal      |         Milestone:
             Component:  Compiler    |           Version:  7.11
  (Type checker)                     |  Operating System:  Linux
              Keywords:              |   Type of failure:  Incorrect
  typechecker plugin cycle imports   |  warning at compile-time
          Architecture:  x86_64      |        Blocked By:
  (amd64)                            |   Related Tickets:
             Test Case:              |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------
 I am playing around with the new type checker plugins using the current
 development branch of GHC. When I supply the plugin module to GHC through
 the command line I get a cyclic import error message, which I think is
 false. If I supply the same plugin module using a pragma I do not get an
 error message.

 === Minimal Example (Command Line)

 `MyPlugin.hs`:
 {{{#!hs
 module MyPlugin ( plugin ) where

 import Plugins ( Plugin, defaultPlugin )

 plugin :: Plugin
 plugin = defaultPlugin
 }}}

 `Test.hs`:
 {{{#!hs
 module Test where

 main :: IO ()
 main = return ()
 }}}

 Command line call of GHC:
 {{{
 ~/ghc/inplace/bin/ghc-stage2 \
   --make
   -package ghc-7.11.20150209 \
   -fplugin=MyPlugin \
   Test.hs
 }}}

 Results in the following error
 {{{
 Module imports form a cycle:
   module ‘MyPlugin’ (./MyPlugin.hs) imports itself
 }}}
 which does not seem reasonable to me understand.

 === Minimal example (pragma)

 On the other hand, if I change `Test.hs` to the following
 {{{#!hs
 {-# OPTIONS_GHC -fplugin MyPlugin #-}
 module Test where

 main :: IO ()
 main = return ()
 }}}

 and calling GHC like this
 {{{
 ~/ghc/inplace/bin/ghc-stage2 \
   --make \
   -package ghc-7.11.20150209 \
   -dynamic \
   Test.hs
 }}}
 it works.

 I did not change `MyPlugin.hs`.

 === Note

  1. Using `-fplugin=MyPlugin` vs. `-fplugin MyPlugin` does not make a
 difference.
  1. The command line example behaves the same independent of whether I
 supply the `-dynamic` flag or not.
  1. I had to add the `-dynamic` flag, because otherwise GHC will complain
 that:
  {{{
  <no location info>:
      cannot find normal object file ‘./MyPlugin.dyn_o’
      while linking an interpreted expression
  }}}
  This might be a long shot, but maybe using the `-fplugin` option should
 imply the `-dynamic` flag?

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


More information about the ghc-tickets mailing list