{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE CPP #-}
#include "ghc-api-version.h"
module Development.IDE.Spans.Documentation (
getDocumentation
, getDocumentationTryGhc
, getDocumentationsTryGhc
) where
import Control.Monad
import Data.Foldable
import Data.List.Extra
import qualified Data.Map as M
import Data.Maybe
import qualified Data.Text as T
#if MIN_GHC_API_VERSION(8,6,0)
import Development.IDE.Core.Compile
#endif
import Development.IDE.GHC.Compat
import Development.IDE.GHC.Error
import Development.IDE.Spans.Common
import System.Directory
import System.FilePath
import FastString
import SrcLoc (RealLocated)
import GhcMonad
import Packages
import Name
getDocumentationTryGhc :: GhcMonad m => Module -> [ParsedModule] -> Name -> m SpanDoc
getDocumentationTryGhc mod deps n = head <$> getDocumentationsTryGhc mod deps [n]
getDocumentationsTryGhc :: GhcMonad m => Module -> [ParsedModule] -> [Name] -> m [SpanDoc]
#if MIN_GHC_API_VERSION(8,6,0)
getDocumentationsTryGhc mod sources names = do
res <- catchSrcErrors "docs" $ getDocsBatch mod names
case res of
Left _ -> mapM mkSpanDocText names
Right res -> zipWithM unwrap res names
where
unwrap (Right (Just docs, _)) n = SpanDocString <$> pure docs <*> getUris n
unwrap _ n = mkSpanDocText n
#else
getDocumentationsTryGhc _ sources names = mapM mkSpanDocText names
where
#endif
mkSpanDocText name =
pure (SpanDocText (getDocumentation sources name)) <*> getUris name
getUris name = do
df <- getSessionDynFlags
(docFp, srcFp) <-
case nameModule_maybe name of
Just mod -> liftIO $ do
doc <- fmap (fmap T.pack) $ lookupDocHtmlForModule df mod
src <- fmap (fmap T.pack) $ lookupSrcHtmlForModule df mod
return (doc, src)
Nothing -> pure (Nothing, Nothing)
let docUri = docFp >>= \fp -> pure $ "file://" <> fp <> "#" <> selector <> showName name
srcUri = srcFp >>= \fp -> pure $ "file://" <> fp <> "#" <> showName name
selector
| isValName name = "v:"
| otherwise = "t:"
return $ SpanDocUris docUri srcUri
getDocumentation
:: HasSrcSpan name
=> [ParsedModule]
-> name
-> [T.Text]
getDocumentation sources targetName = fromMaybe [] $ do
targetNameSpan <- realSpan $ getLoc targetName
tc <-
find ((==) (Just $ srcSpanFile targetNameSpan) . annotationFileName)
$ reverse sources
let bs = [ n | let L _ HsModule{hsmodDecls} = pm_parsed_source tc
, L _ (ValD hsbind) <- hsmodDecls
, Just n <- [name_of_bind hsbind]
]
let sortedSpans = sortedNameSpans bs
let docs = ann tc
nameInd <- elemIndex targetNameSpan sortedSpans
let prevNameSpan =
if nameInd >= 1
then sortedSpans !! (nameInd - 1)
else zeroSpan $ srcSpanFile targetNameSpan
pure
$ docHeaders
$ filter (\(L target _) -> isBetween target prevNameSpan targetNameSpan)
$ mapMaybe (\(L l v) -> L <$> realSpan l <*> pure v)
$ join
$ M.elems
docs
where
name_of_bind :: HsBind GhcPs -> Maybe (Located RdrName)
name_of_bind FunBind {fun_id} = Just fun_id
name_of_bind _ = Nothing
sortedNameSpans :: [Located RdrName] -> [RealSrcSpan]
sortedNameSpans ls = nubSort (mapMaybe (realSpan . getLoc) ls)
isBetween target before after = before <= target && target <= after
ann = snd . pm_annotations
annotationFileName :: ParsedModule -> Maybe FastString
annotationFileName = fmap srcSpanFile . listToMaybe . realSpans . ann
realSpans :: M.Map SrcSpan [Located a] -> [RealSrcSpan]
realSpans =
mapMaybe (realSpan . getLoc)
. join
. M.elems
docHeaders :: [RealLocated AnnotationComment]
-> [T.Text]
docHeaders = mapMaybe (\(L _ x) -> wrk x)
where
wrk = \case
AnnDocCommentNext s -> Just $ T.pack s
AnnLineComment s -> if "-- |" `isPrefixOf` s
then Just $ T.pack s
else Nothing
_ -> Nothing
lookupDocHtmlForModule :: DynFlags -> Module -> IO (Maybe FilePath)
lookupDocHtmlForModule =
lookupHtmlForModule (\pkgDocDir modDocName -> pkgDocDir </> modDocName <.> "html")
lookupSrcHtmlForModule :: DynFlags -> Module -> IO (Maybe FilePath)
lookupSrcHtmlForModule =
lookupHtmlForModule (\pkgDocDir modDocName -> pkgDocDir </> "src" </> modDocName <.> "html")
lookupHtmlForModule :: (FilePath -> FilePath -> FilePath) -> DynFlags -> Module -> IO (Maybe FilePath)
lookupHtmlForModule mkDocPath df m = do
let mfs = go <$> (listToMaybe =<< lookupHtmls df ui)
htmls <- filterM doesFileExist (concat . maybeToList $ mfs)
return $ listToMaybe htmls
where
go pkgDocDir = [mkDocPath pkgDocDir mn | mn <- [mndot,mndash]]
ui = moduleUnitId m
mndash = map (\x -> if x == '.' then '-' else x) mndot
mndot = moduleNameString $ moduleName m
lookupHtmls :: DynFlags -> UnitId -> Maybe [FilePath]
lookupHtmls df ui = haddockHTMLs <$> lookupPackage df ui