[GHC] #11301: Using GHC's parser and rendering the results is unreasonably difficult

GHC ghc-devs at haskell.org
Mon Dec 28 05:47:51 UTC 2015


#11301: Using GHC's parser and rendering the results is unreasonably difficult
-------------------------------------+-------------------------------------
        Reporter:  bitemyapp         |                Owner:
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  GHC API           |              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:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by ezyang):

 Have you considered getting a recent build of GHC 8 and doing this as a
 frontend plugin? Here's something that works for a recent GHC build:

 {{{
 module Print where

 import GhcPlugins

 import DynFlags
 import FastString
 import GhcMonad
 import DriverPhases
 import HsSyn
 import Lexer
 import Outputable
 import Parser
 import RdrName
 import SrcLoc
 import StaticFlags
 import StringBuffer
 import ErrUtils

 import Control.Monad

 frontendPlugin :: FrontendPlugin
 frontendPlugin = defaultFrontendPlugin {
         frontend = doPrint
     }

 doPrint :: [String] -> [(String, Maybe Phase)] -> Ghc ()
 doPrint args [] = error "usage: ghc --frontend Print File.hs"
 doPrint args fs = do
     dflags <- getDynFlags
     forM_ fs $ \(src_filename, _) -> do
         buf <- liftIO $ hGetStringBuffer src_filename
         let loc = mkRealSrcLoc (mkFastString src_filename) 1 1
         case unP parseModule (mkPState dflags buf loc) of
             PFailed span err ->
                 liftIO $ throwOneError (mkPlainErrMsg dflags span err)
             POk pst rdr_module ->
                 liftIO . putStrLn $ showSDoc dflags (ppr rdr_module)
 }}}

 Here's how to build and run it;

 {{{
 ghc --make Print.hs -package ghc -dynamic-too
 ghc --frontend Print Print.hs
 }}}

 Evidently, we should expose some sort of function which takes just a file
 name (rather than a `ModSummary`, which is a little touchy to get). This
 should be simple enough for someone to add.

 And I agree: static/dynamic flag initialization is terrible. It would be
 well worth someone trying to see if we can (finally) get rid of the rest
 of the static flags. It would also be useful to know what kind of
 abstracting API people would like to get dumped into the `Ghc` monad with
 minimum fuss. There IS some fuss involved; for example, it's convenient to
 have GHC's options parser around so that `DynFlags` are as configurable as
 they are with GHC. Would love proposals! (Willing to improve it, but it's
 very unclear what a good interface is supposed to be. One of the reasons I
 wrote the frontend plugins patch instead.)

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


More information about the ghc-tickets mailing list