{-# OPTIONS_GHC -Wwarn #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ViewPatterns #-}
module Haddock.Interface.LexParseRn
( processDocString
, processDocStringParas
, processDocStrings
, processModuleHeader
) where
import Avail
import Control.Arrow
import Control.Monad
import Data.List
import Data.Ord
import Documentation.Haddock.Doc (metaDocConcat)
import DynFlags (languageExtensions)
import qualified GHC.LanguageExtensions as LangExt
import GHC
import Haddock.Interface.ParseModuleHeader
import Haddock.Parser
import Haddock.Types
import Name
import Outputable ( showPpr, showSDoc )
import RdrName
import EnumSet
import RnEnv (dataTcOccs)
processDocStrings :: DynFlags -> Maybe Package -> GlobalRdrEnv -> [HsDocString]
-> ErrMsgM (Maybe (MDoc Name))
processDocStrings dflags pkg gre strs = do
mdoc <- metaDocConcat <$> traverse (processDocStringParas dflags pkg gre) strs
case mdoc of
MetaDoc { _meta = Meta Nothing Nothing, _doc = DocEmpty } -> pure Nothing
x -> pure (Just x)
processDocStringParas :: DynFlags -> Maybe Package -> GlobalRdrEnv -> HsDocString -> ErrMsgM (MDoc Name)
processDocStringParas dflags pkg gre hds =
overDocF (rename dflags gre) $ parseParas dflags pkg (unpackHDS hds)
processDocString :: DynFlags -> GlobalRdrEnv -> HsDocString -> ErrMsgM (Doc Name)
processDocString dflags gre hds =
rename dflags gre $ parseString dflags (unpackHDS hds)
processModuleHeader :: DynFlags -> Maybe Package -> GlobalRdrEnv -> SafeHaskellMode -> Maybe LHsDocString
-> ErrMsgM (HaddockModInfo Name, Maybe (MDoc Name))
processModuleHeader dflags pkgName gre safety mayStr = do
(hmi, doc) <-
case mayStr of
Nothing -> return failure
Just (L _ hds) -> do
let str = unpackHDS hds
(hmi, doc) = parseModuleHeader dflags pkgName str
!descr <- case hmi_description hmi of
Just hmi_descr -> Just <$> rename dflags gre hmi_descr
Nothing -> pure Nothing
let hmi' = hmi { hmi_description = descr }
doc' <- overDocF (rename dflags gre) doc
return (hmi', Just doc')
let flags :: [LangExt.Extension]
flags = EnumSet.toList (extensionFlags dflags) \\ languageExtensions (language dflags)
return (hmi { hmi_safety = Just $ showPpr dflags safety
, hmi_language = language dflags
, hmi_extensions = flags
} , doc)
where
failure = (emptyHaddockModInfo, Nothing)
rename :: DynFlags -> GlobalRdrEnv -> Doc RdrName -> ErrMsgM (Doc Name)
rename dflags gre = rn
where
rn d = case d of
DocAppend a b -> DocAppend <$> rn a <*> rn b
DocParagraph doc -> DocParagraph <$> rn doc
DocIdentifier x -> do
let choices = dataTcOccs x
case concatMap (\c -> lookupGRE_RdrName c gre) choices of
[] ->
case choices of
[] -> pure (DocMonospaced (DocString (showPpr dflags x)))
a:_ -> outOfScope dflags a
[a] -> pure (DocIdentifier (gre_name a))
gres -> ambiguous dflags x gres
DocWarning doc -> DocWarning <$> rn doc
DocEmphasis doc -> DocEmphasis <$> rn doc
DocBold doc -> DocBold <$> rn doc
DocMonospaced doc -> DocMonospaced <$> rn doc
DocUnorderedList docs -> DocUnorderedList <$> traverse rn docs
DocOrderedList docs -> DocOrderedList <$> traverse rn docs
DocDefList list -> DocDefList <$> traverse (\(a, b) -> (,) <$> rn a <*> rn b) list
DocCodeBlock doc -> DocCodeBlock <$> rn doc
DocIdentifierUnchecked x -> pure (DocIdentifierUnchecked x)
DocModule str -> pure (DocModule str)
DocHyperlink l -> pure (DocHyperlink l)
DocPic str -> pure (DocPic str)
DocMathInline str -> pure (DocMathInline str)
DocMathDisplay str -> pure (DocMathDisplay str)
DocAName str -> pure (DocAName str)
DocProperty p -> pure (DocProperty p)
DocExamples e -> pure (DocExamples e)
DocEmpty -> pure (DocEmpty)
DocString str -> pure (DocString str)
DocHeader (Header l t) -> DocHeader . Header l <$> rn t
DocTable t -> DocTable <$> traverse rn t
outOfScope :: DynFlags -> RdrName -> ErrMsgM (Doc a)
outOfScope dflags x =
case x of
Unqual occ -> warnAndMonospace occ
Qual mdl occ -> pure (DocIdentifierUnchecked (mdl, occ))
Orig _ occ -> warnAndMonospace occ
Exact name -> warnAndMonospace name
where
warnAndMonospace a = do
tell ["Warning: '" ++ showPpr dflags a ++ "' is out of scope.\n" ++
" If you qualify the identifier, haddock can try to link it\n" ++
" it anyway."]
pure (monospaced a)
monospaced a = DocMonospaced (DocString (showPpr dflags a))
ambiguous :: DynFlags
-> RdrName
-> [GlobalRdrElt]
-> ErrMsgM (Doc Name)
ambiguous dflags x gres = do
let noChildren = map availName (gresToAvailInfo gres)
dflt = maximumBy (comparing (isLocalName &&& isTyConName)) noChildren
msg = "Warning: " ++ x_str ++ " is ambiguous. It is defined\n" ++
concatMap (\n -> " * " ++ defnLoc n ++ "\n") (map gre_name gres) ++
" You may be able to disambiguate the identifier by qualifying it or\n" ++
" by hiding some imports.\n" ++
" Defaulting to " ++ x_str ++ " defined " ++ defnLoc dflt
when (length noChildren > 1) $ tell [msg]
pure (DocIdentifier dflt)
where
isLocalName (nameSrcLoc -> RealSrcLoc {}) = True
isLocalName _ = False
x_str = '\'' : showPpr dflags x ++ "'"
defnLoc = showSDoc dflags . pprNameDefnLoc