[GHC] #8945: GHC produces grouped declarations in a weird order

GHC ghc-devs at haskell.org
Mon Mar 31 21:41:25 UTC 2014


#8945: GHC produces grouped declarations in a weird order
------------------------------------+-------------------------------------
       Reporter:  Fuuzetsu          |             Owner:
           Type:  bug               |            Status:  new
       Priority:  normal            |         Milestone:
      Component:  GHC API           |           Version:  7.9
       Keywords:                    |  Operating System:  Unknown/Multiple
   Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
     Difficulty:  Unknown           |         Test Case:
     Blocked By:                    |          Blocking:
Related Tickets:                    |
------------------------------------+-------------------------------------
 Consider very simple module like

 {{{#!haskell
 module J where

 class A a where
   f, g, h, i :: a -> ()
 }}}

 Now when we ask GHC about declarations in the module and extract function
 signatures, we don't get {{{f, g, h, i :: a -> ()}}} as we could expect.
 We instead get {{{f, i, h, g :: a -> ()}}}. The pattern is that the first
 name is in a correct position and the rest is reversed. This leads to
 whatever uses the API get the names in order different than that in the
 source file. See http://trac.haskell.org/haddock/ticket/188 for an example
 when this matters.

 I have prepared an example using GHC API which you can run on your machine
 with your own test files and see the results for yourselves.

 {{{#!haskell
 -- GHC.Paths requires the very small ghc-paths package.
 -- if you don't want it, libdir = ghc --print-libdir
 module Main where

 import Control.Monad (ap, liftM2)
 import Data.Functor ((<$>))
 import System.Environment (getArgs)

 import Digraph (flattenSCCs)
 import GHC
 import GHC.Paths (libdir)
 import Outputable (text, ppr, showSDoc, (<>), (<+>))

 main :: IO ()
 main = do
   (dfs, modules) <- getArgs >>= withGhc Nothing . processModules
   let r = map (showSDoc dfs . (\(x,y) -> text x <> text ":" <+> ppr y)  .
 f)
             modules
   putStrLn $ unlines r
   where
     f (s, t) = (ms_hspp_file s, (\(x,_,_,_) -> x) <$> tm_renamed_source t)

 type ModuleName' = String

 withGhc :: Maybe DynFlags -> Ghc a -> IO (DynFlags, a)
 withGhc d act =
   runGhc (Just libdir) $ do
     dynflags <- case d of
       Nothing -> getSessionDynFlags
       Just d' -> return d'

     _ <- setSessionDynFlags dynflags
     liftM2 (,) getSessionDynFlags act

 processModules :: [ModuleName']
                -> Ghc [(ModSummary, TypecheckedModule)]
 processModules modules = do
   mg <- depAnalysis
   let sortedMods = flattenSCCs $ topSortModuleGraph False mg Nothing
   mapM (\x -> return (\y -> (x,y)) `ap`
               (parseModule x >>= typecheckModule >>= loadModule))
     sortedMods
   where
     depAnalysis :: Ghc ModuleGraph
     depAnalysis = do
       targets <- mapM (\f -> guessTarget f Nothing) modules
       setTargets targets
       depanal [] False
 }}}

 In this case, using the tiny module I posted at the beginning, I get:
 {{{
 *Main> :main "/tmp/J.hs"
 /tmp/J.hs: Just class J.A a where
                   J.f, J.i, J.h, J.g :: a -> ()
 }}}

 It looks to me like it's just an oversight somewhere in the API and should
 be an easy fix for someone familiar with that part. I'd rather save myself
 many hours trying to find it on my own.

 PS: Are the rules for when grouping happens documented somewhere? Grouping
 functions in class definitions is the only sure-fire way I can get a
 grouped signature but I'm sure there were others in the past that no
 longer work.

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


More information about the ghc-tickets mailing list