1- {-# LANGUAGE CPP, OverloadedStrings, BangPatterns #-}
1+ {-# LANGUAGE CPP, OverloadedStrings, BangPatterns, NamedFieldPuns #-}
22-----------------------------------------------------------------------------
33-- |
44-- Module : Haddock.Interface
2929-- using this environment.
3030-----------------------------------------------------------------------------
3131module Haddock.Interface (
32- processModules
32+ plugin
33+ , processModules
3334) where
3435
3536
@@ -43,26 +44,30 @@ import Haddock.Types
4344import Haddock.Utils
4445
4546import Control.Monad
46- import Control.Monad.IO.Class ( liftIO )
47- import Control.Exception ( evaluate )
47+ import Control.Monad.IO.Class ( MonadIO ( liftIO ) )
48+ import Data.IORef
4849import Data.List (foldl' , isPrefixOf , nub )
4950import qualified Data.Map as Map
5051import qualified Data.Set as Set
5152import Text.Printf
5253
53- import GHC.Unit.Module.Env ( mkModuleSet , emptyModuleSet , unionModuleSet , ModuleSet )
54+ import GHC hiding ( verbosity )
5455import GHC.Data.Graph.Directed
5556import GHC.Driver.Session hiding (verbosity )
56- import GHC hiding ( verbosity )
57- import GHC.Driver.Types
57+ import GHC.Driver.Types ( isBootSummary )
58+ import GHC.Driver.Monad ( Session ( .. ), modifySession , reflectGhc )
5859import GHC.Data.FastString (unpackFS )
59- import GHC.Tc.Types (tcg_rdr_env )
60+ import GHC.Tc.Types (TcGblEnv (.. ))
61+ import GHC.Tc.Utils.Monad (getTopEnv )
6062import GHC.Types.Name (nameIsFromExternalPackage , nameOccName )
6163import GHC.Types.Name.Occurrence (isTcOcc )
6264import GHC.Types.Name.Reader (unQualOK , gre_name , globalRdrEnvElts )
65+ import GHC.Unit.Module.Env (mkModuleSet , emptyModuleSet , unionModuleSet , ModuleSet )
66+ import GHC.Unit.Types (IsBootInterface (.. ))
6367import GHC.Utils.Error (withTimingD )
6468import GHC.HsToCore.Docs
65- import GHC.Runtime.Loader (initializePlugins )
69+ import GHC.Plugins (HscEnv (.. ), Outputable , StaticPlugin (.. ), Plugin (.. ), PluginWithArgs (.. ),
70+ defaultPlugin , keepRenamedSource )
6671
6772#if defined(mingw32_HOST_OS)
6873import System.IO
@@ -88,8 +93,14 @@ processModules verbosity modules flags extIfaces = do
8893#endif
8994
9095 out verbosity verbose " Creating interfaces..."
91- let instIfaceMap = Map. fromList [ (instMod iface, iface) | ext <- extIfaces
92- , iface <- ifInstalledIfaces ext ]
96+ let
97+ instIfaceMap :: InstIfaceMap
98+ instIfaceMap = Map. fromList
99+ [ (instMod iface, iface)
100+ | ext <- extIfaces
101+ , iface <- ifInstalledIfaces ext
102+ ]
103+
93104 (interfaces, ms) <- createIfaces verbosity modules flags instIfaceMap
94105
95106 let exportedNames =
@@ -125,104 +136,204 @@ processModules verbosity modules flags extIfaces = do
125136
126137createIfaces :: Verbosity -> [String ] -> [Flag ] -> InstIfaceMap -> Ghc ([Interface ], ModuleSet )
127138createIfaces verbosity modules flags instIfaceMap = do
128- -- Ask GHC to tell us what the module graph is
139+ (haddockPlugin, getIfaces, getModules) <- liftIO $ plugin
140+ verbosity flags instIfaceMap
141+
142+ let
143+ installHaddockPlugin :: HscEnv -> HscEnv
144+ installHaddockPlugin hsc_env = hsc_env
145+ {
146+ hsc_dflags = (gopt_set (hsc_dflags hsc_env) Opt_PluginTrustworthy )
147+ {
148+ staticPlugins = haddockPlugin : staticPlugins (hsc_dflags hsc_env)
149+ }
150+ }
151+
152+ -- Note that we would rather use withTempSession but as long as we
153+ -- have the separate attachInstances step we need to keep the session
154+ -- alive to be able to find all the instances.
155+ modifySession installHaddockPlugin
156+
129157 targets <- mapM (\ filePath -> guessTarget filePath Nothing ) modules
130158 setTargets targets
131- modGraph <- depanal [] False
132159
133- -- Visit modules in that order
134- let sortedMods = flattenSCCs $ topSortModuleGraph False modGraph Nothing
135- out verbosity normal " Haddock coverage:"
136- (ifaces, _, ! ms) <- foldM f ([] , Map. empty, emptyModuleSet) sortedMods
137- return (reverse ifaces, ms)
138- where
139- f (ifaces, ifaceMap, ! ms) modSummary = do
140- x <- {-# SCC processModule #-}
141- withTimingD " processModule" (const () ) $ do
142- processModule verbosity modSummary flags ifaceMap instIfaceMap
143- return $ case x of
144- Just (iface, ms') -> ( iface: ifaces
145- , Map. insert (ifaceMod iface) iface ifaceMap
146- , unionModuleSet ms ms' )
147- Nothing -> ( ifaces
148- , ifaceMap
149- , ms ) -- Boot modules don't generate ifaces.
150-
151-
152- processModule :: Verbosity -> ModSummary -> [Flag ] -> IfaceMap -> InstIfaceMap -> Ghc (Maybe (Interface , ModuleSet ))
153- processModule verbosity modsum flags modMap instIfaceMap = do
154- out verbosity verbose $ " Checking module " ++ moduleString (ms_mod modsum) ++ " ..."
155-
156- -- Since GHC 8.6, plugins are initialized on a per module basis
157- hsc_env' <- getSession
158- dynflags' <- liftIO (initializePlugins hsc_env' (GHC. ms_hspp_opts modsum))
159- let modsum' = modsum { ms_hspp_opts = dynflags' }
160-
161- tm <- {-# SCC "parse/typecheck/load" #-} loadModule =<< typecheckModule =<< parseModule modsum'
162-
163- case isBootSummary modsum of
164- IsBoot ->
165- return Nothing
166- NotBoot -> do
167- out verbosity verbose " Creating interface..."
160+ loadOk <- withTimingD " load" (const () ) $
161+ {-# SCC load #-} GHC. load LoadAllTargets
162+
163+ case loadOk of
164+ Failed ->
165+ throwE " Cannot typecheck modules"
166+ Succeeded -> do
167+ modGraph <- GHC. getModuleGraph
168+ ifaceMap <- liftIO getIfaces
169+ moduleSet <- liftIO getModules
168170
169171 let
170- mod_summary = pm_mod_summary (tm_parsed_module tm)
171- tcg_gbl_env = fst (tm_internals_ tm)
172-
173- (interface, msgs) <- {-# SCC createIterface #-}
174- withTimingD " createInterface" (const () ) $ do
175- runWriterGhc $ createInterface1 flags mod_summary
176- tcg_gbl_env modMap instIfaceMap
177-
178- -- We need to keep track of which modules were somehow in scope so that when
179- -- Haddock later looks for instances, it also looks in these modules too.
180- --
181- -- See https://github.com/haskell/haddock/issues/469.
182- hsc_env <- getSession
183- let new_rdr_env = tcg_rdr_env . fst . GHC. tm_internals_ $ tm
184- this_pkg = homeUnit (hsc_dflags hsc_env)
185- ! mods = mkModuleSet [ nameModule name
186- | gre <- globalRdrEnvElts new_rdr_env
187- , let name = gre_name gre
188- , nameIsFromExternalPackage this_pkg name
189- , isTcOcc (nameOccName name) -- Types and classes only
190- , unQualOK gre ] -- In scope unqualified
191-
192- liftIO $ mapM_ putStrLn (nub msgs)
193- dflags <- getDynFlags
194- let (haddockable, haddocked) = ifaceHaddockCoverage interface
195- percentage = div (haddocked * 100 ) haddockable
196- modString = moduleString (ifaceMod interface)
197- coverageMsg = printf " %3d%% (%3d /%3d) in '%s'" percentage haddocked haddockable modString
198- header = case ifaceDoc interface of
199- Documentation Nothing _ -> False
200- _ -> True
201- undocumentedExports = [ formatName s n | ExportDecl { expItemDecl = L s n
202- , expItemMbDoc = (Documentation Nothing _, _)
203- } <- ifaceExportItems interface ]
204- where
205- formatName :: SrcSpan -> HsDecl GhcRn -> String
206- formatName loc n = p (getMainDeclBinder n) ++ case loc of
207- RealSrcSpan rss _ -> " (" ++ unpackFS (srcSpanFile rss) ++ " :" ++ show (srcSpanStartLine rss) ++ " )"
208- _ -> " "
209-
210- p [] = " "
211- p (x: _) = let n = pretty dflags x
212- ms = modString ++ " ."
213- in if ms `isPrefixOf` n
214- then drop (length ms) n
215- else n
216-
217- when (OptHide `notElem` ifaceOptions interface) $ do
218- out verbosity normal coverageMsg
219- when (Flag_NoPrintMissingDocs `notElem` flags
220- && not (null undocumentedExports && header)) $ do
221- out verbosity normal " Missing documentation for:"
222- unless header $ out verbosity normal " Module header"
223- mapM_ (out verbosity normal . (" " ++ )) undocumentedExports
224- interface' <- liftIO $ evaluate interface
225- return (Just (interface', mods))
172+ ifaces :: [Interface ]
173+ ifaces =
174+ [ Map. findWithDefault
175+ (error " haddock:iface" )
176+ (ms_mod ms)
177+ ifaceMap
178+ | ms <- flattenSCCs $ topSortModuleGraph True modGraph Nothing
179+ ]
180+
181+ return (ifaces, moduleSet)
182+
183+
184+ -- | A `Plugin` that hooks into GHC's compilation pipeline to generate Haddock
185+ -- interfaces. Due to the plugin nature we benefit from GHC's capabilities to
186+ -- parallelize the compilation process.
187+ plugin
188+ :: MonadIO m
189+ => Verbosity
190+ -> [Flag ]
191+ -> InstIfaceMap
192+ -> m
193+ (
194+ StaticPlugin -- the plugin to install with GHC
195+ , m IfaceMap -- get the processed interfaces
196+ , m ModuleSet -- get the loaded modules
197+ )
198+ plugin verbosity flags instIfaceMap = liftIO $ do
199+ ifaceMapRef <- newIORef Map. empty
200+ moduleSetRef <- newIORef emptyModuleSet
201+
202+ let
203+ processTypeCheckedResult :: ModSummary -> TcGblEnv -> Ghc ()
204+ processTypeCheckedResult mod_summary tc_gbl_env
205+ -- Don't do anything for hs-boot modules
206+ | IsBoot <- isBootSummary mod_summary =
207+ pure ()
208+ | otherwise = do
209+ ifaces <- liftIO $ readIORef ifaceMapRef
210+ (iface, modules) <- withTimingD " processModule" (const () ) $
211+ processModule1 verbosity flags ifaces instIfaceMap mod_summary tc_gbl_env
212+
213+ liftIO $ do
214+ atomicModifyIORef' ifaceMapRef $ \ xs ->
215+ (Map. insert (ms_mod mod_summary) iface xs, () )
216+
217+ atomicModifyIORef' moduleSetRef $ \ xs ->
218+ (modules `unionModuleSet` xs, () )
219+
220+ staticPlugin :: StaticPlugin
221+ staticPlugin = StaticPlugin
222+ {
223+ spPlugin = PluginWithArgs
224+ {
225+ paPlugin = defaultPlugin
226+ {
227+ renamedResultAction = keepRenamedSource
228+ , typeCheckResultAction = \ _ mod_summary tc_gbl_env -> do
229+ session <- getTopEnv >>= liftIO . newIORef
230+ liftIO $ reflectGhc
231+ (processTypeCheckedResult mod_summary tc_gbl_env)
232+ (Session session)
233+ pure tc_gbl_env
234+
235+ }
236+ , paArguments = []
237+ }
238+ }
239+
240+ pure
241+ ( staticPlugin
242+ , liftIO (readIORef ifaceMapRef)
243+ , liftIO (readIORef moduleSetRef)
244+ )
245+
246+
247+
248+ processModule1
249+ :: Verbosity
250+ -> [Flag ]
251+ -> IfaceMap
252+ -> InstIfaceMap
253+ -> ModSummary
254+ -> TcGblEnv
255+ -> Ghc (Interface , ModuleSet )
256+ processModule1 verbosity flags ifaces inst_ifaces mod_summary tc_gbl_env = do
257+ out verbosity verbose " Creating interface..."
258+
259+ let
260+ TcGblEnv { tcg_rdr_env } = tc_gbl_env
261+
262+ (! interface, messages) <- {-# SCC createInterface #-}
263+ withTimingD " createInterface" (const () ) $
264+ runWriterGhc $ createInterface1 flags mod_summary
265+ tc_gbl_env ifaces inst_ifaces
266+
267+ -- We need to keep track of which modules were somehow in scope so that when
268+ -- Haddock later looks for instances, it also looks in these modules too.
269+ --
270+ -- See https://github.com/haskell/haddock/issues/469.
271+
272+ dflags <- getDynFlags
273+ let
274+ mods :: ModuleSet
275+ ! mods = mkModuleSet
276+ [ nameModule name
277+ | gre <- globalRdrEnvElts tcg_rdr_env
278+ , let name = gre_name gre
279+ , nameIsFromExternalPackage (homeUnit dflags) name
280+ , isTcOcc (nameOccName name) -- Types and classes only
281+ , unQualOK gre -- In scope unqualified
282+ ]
283+
284+ liftIO $ mapM_ putStrLn (nub messages)
285+
286+ let
287+ (haddockable, haddocked) =
288+ ifaceHaddockCoverage interface
289+
290+ percentage :: Int
291+ percentage =
292+ round (fromIntegral haddocked * 100 / fromIntegral haddockable :: Double )
293+
294+ modString :: String
295+ modString = moduleString (ifaceMod interface)
296+
297+ coverageMsg :: String
298+ coverageMsg =
299+ printf " %3d%% (%3d /%3d) in '%s'" percentage haddocked haddockable modString
300+
301+ header :: Bool
302+ header = case ifaceDoc interface of
303+ Documentation Nothing _ -> False
304+ _ -> True
305+
306+ undocumentedExports :: [String ]
307+ undocumentedExports =
308+ [ formatName s n
309+ | ExportDecl { expItemDecl = L s n
310+ , expItemMbDoc = (Documentation Nothing _, _)
311+ } <- ifaceExportItems interface
312+ ]
313+ where
314+ formatName :: SrcSpan -> HsDecl GhcRn -> String
315+ formatName loc n = p (getMainDeclBinder n) ++ case loc of
316+ RealSrcSpan rss _ -> " (" ++ unpackFS (srcSpanFile rss) ++ " :" ++
317+ show (srcSpanStartLine rss) ++ " )"
318+ _ -> " "
319+
320+ p :: Outputable a => [a ] -> String
321+ p [] = " "
322+ p (x: _) = let n = pretty dflags x
323+ ms = modString ++ " ."
324+ in if ms `isPrefixOf` n
325+ then drop (length ms) n
326+ else n
327+
328+ when (OptHide `notElem` ifaceOptions interface) $ do
329+ out verbosity normal coverageMsg
330+ when (Flag_NoPrintMissingDocs `notElem` flags
331+ && not (null undocumentedExports && header)) $ do
332+ out verbosity normal " Missing documentation for:"
333+ unless header $ out verbosity normal " Module header"
334+ mapM_ (out verbosity normal . (" " ++ )) undocumentedExports
335+
336+ pure (interface, mods)
226337
227338
228339--------------------------------------------------------------------------------
0 commit comments