[GHC] #11579: Bug in parser for named Haddock chunks since GHC 8.0.1-rc1
GHC
ghc-devs at haskell.org
Tue Feb 16 20:13:27 UTC 2016
#11579: Bug in parser for named Haddock chunks since GHC 8.0.1-rc1
-------------------------------------+-------------------------------------
Reporter: SimonHengel | Owner:
Type: bug | Status: new
Priority: high | Milestone: 8.0.1
Component: Compiler | Version: 8.0.1-rc2
(Parser) |
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: |
-------------------------------------+-------------------------------------
Changes (by bgamari):
* priority: normal => high
* component: Compiler => Compiler (Parser)
* milestone: => 8.0.1
@@ -3,1 +3,1 @@
- {{{
+ {{{#!hs
@@ -11,1 +11,1 @@
- {{{
+ {{{#!hs
New description:
Steps to reproduce:
{{{#!hs
-- Foo.hs
module Foo where
-- $bar some
-- named chunk
}}}
{{{#!hs
-- Extract.hs
module Extract where
import Prelude hiding (mod)
import Data.Generics
import DynFlags
import FastString
import GHC
import GHC.Paths
extractDocStrings :: IO [String]
extractDocStrings = do
extract . pm_parsed_source <$> do
runGhc (Just libdir) $ do
_ <- getSessionDynFlags >>= setSessionDynFlags . setHaddockMode
guessTarget "Foo.hs" Nothing >>= setTargets . return
[mod] <- depanal [] False
parseModule mod
where
setHaddockMode :: DynFlags -> DynFlags
setHaddockMode dynflags = (gopt_set dynflags Opt_Haddock)
extract :: ParsedSource -> [String]
extract m = [unpackFS s | HsDocString s <- everything (++) ([] `mkQ`
return) m]
}}}
Expected result: {{{extractDocStrings}}} returns {{{" some\n named
chunk"}}}
Actual result: it returns {{{" some"}}} instead
--
Comment:
Oh dear, this should get fixed.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11579#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list