#2584: Pretty printing of types with HsDocTy goes wrong
-----------------------------+----------------------------------------------
    Reporter:  NeilMitchell  |       Owner:          
        Type:  bug           |      Status:  new     
    Priority:  normal        |   Component:  Compiler
     Version:  6.9           |    Severity:  major   
    Keywords:                |    Testcase:          
Architecture:  Unknown       |          Os:  Unknown 
-----------------------------+----------------------------------------------
 Pretty printing of type signatures containing HsDocTy goes wrong in HEAD.
 This manifests itself as serious bugs in both Haddock and Hoogle. Because
 the bug causes Haddock generated documentation to be wrong, I've marked
 the severity as major.

 Take the following file:

 {{{
 {-# LANGUAGE FlexibleInstances #-}

 import GHC
 import SrcLoc
 import Outputable

 main = do
         putStrLn $ out $ HsFunTy fun fun
         putStrLn $ out $ HsFunTy (doc fun) fun

 reL = L undefined
 out x = showSDoc $ ppr x
 fun = reL $ HsFunTy (reL $ HsTyVar "a") (reL $ HsTyVar "b")
 doc = reL . flip HsDocTy undefined

 instance OutputableBndr [Char] where
         pprBndr _ x = text x
 }}}

 The output is:

 {{{
 C:\Neil>runghc "-package ghc" test2.hs
 ([a] -> [b]) -> [a] -> [b]
 [a] -> [b] <document comment> -> [a] -> [b]
 }}}

 Note that the first line (correctly) brackets the type signature, but that
 the second (incorrectly) omits the brackets. I suggest a change to the
 pretty printer to ignore HsTyDoc when determining where to insert brackets
 - or even removing the pretty printing of HsTyDoc entirely.

 -- Neil

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2584>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to