[Haddock] [haddock] #207: haddock: internal error: spliceURL UnhelpfulSpan

haddock haddock at projects.haskell.org
Fri Aug 31 16:34:39 BST 2012


#207: haddock: internal error: spliceURL UnhelpfulSpan
---------------------+------------------------------------------------------
Reporter:  selinger  |        Owner:        
    Type:  defect    |       Status:  new   
Priority:  major     |    Milestone:  2.10.0
 Version:  2.9.4     |   Resolution:        
Keywords:            |  
---------------------+------------------------------------------------------

Comment(by valiron):

 In case anyone is interested, I wrote a patch to solve this problem for
 haddock 2.11.0 and ghc 7.4.2: essentially I filter out the problematic
 items. The net effect is that exported elements without type signature are
 not shown in the documentation.


 {{{
 diff -r -u haddock-ghc-7.4.2/src/Haddock/Interface/Create.hs
 haddock/src/Haddock/Interface/Create.hs
 --- haddock-ghc-7.4.2/src/Haddock/Interface/Create.hs   2012-08-30
 10:12:42.149210546 -0400
 +++ haddock/src/Haddock/Interface/Create.hs     2012-08-30
 10:13:08.745620048 -0400
 @@ -19,6 +19,7 @@
  import Haddock.Utils
  import Haddock.Convert
  import Haddock.Interface.LexParseRn
 +import Haddock.Interface.Rename

  import qualified Data.Map as M
  import Data.Map (Map)
 @@ -41,6 +42,25 @@
  import TcRnTypes
  import FastString (unpackFS)

 +-- | To filter out the ExportItem's that are UnhelpfulSpan.
 +isHelpfulSpan :: ExportItem Name -> ErrMsgM Bool
 +isHelpfulSpan l = case l of
 +     (ExportDecl (L (UnhelpfulSpan _) _) _ _ _) -> do
 +       tell [concat ["Warning: ",
 +                     extractName l,
 +                     " is exported but does not have a type signature. ",
 +                     "Skipping it..."]]
 +       return False
 +     _ -> return True
 +  where
 +
 +  -- This is reusing renameExportItem and runRnFM from
 +  -- Haddock.Interface.Rename.
 +  --
 +  -- We use an empty environment for simplicity: for the sake
 +  -- of the warning, we know in which module this takes place.
 +  extractName :: ExportItem Name -> String
 +  extractName e = show $ getOccString $ head $ snd $ runRnFM M.empty $
 renameExportItem e

  -- | Use a 'TypecheckedModule' to produce an 'Interface'.
  -- To do this, we need access to already processed modules in the
 topological
 @@ -91,6 +111,7 @@
    let warningMap = mkWarningMap warnings gre exportedNames
    exportItems <- mkExportItems modMap mdl warningMap gre exportedNames
 decls maps exports
                     instances instIfaceMap dflags
 +                 >>= (liftErrMsg . filterM isHelpfulSpan)

    let visibleNames = mkVisibleNames exportItems opts

 diff -r -u haddock-ghc-7.4.2/src/Haddock/Interface/Rename.hs
 haddock/src/Haddock/Interface/Rename.hs
 --- haddock-ghc-7.4.2/src/Haddock/Interface/Rename.hs   2012-08-30
 10:12:42.149210546 -0400
 +++ haddock/src/Haddock/Interface/Rename.hs     2012-08-29
 17:12:47.812702645 -0400
 @@ -9,7 +9,7 @@
  -- Stability   :  experimental
  -- Portability :  portable
 -----------------------------------------------------------------------------
 -module Haddock.Interface.Rename (renameInterface) where
 +module Haddock.Interface.Rename
 (renameInterface,renameExportItem,runRnFM) where


  import Haddock.GhcUtils
 }}}

-- 
Ticket URL: <http://trac.haskell.org/haddock/ticket/207#comment:3>
haddock <http://www.haskell.org/haddock>
Haddock, The Haskell Documentation Tool


More information about the Haddock mailing list