aboutsummaryrefslogtreecommitdiff
path: root/haddock-api/src/Haddock/Interface.hs
diff options
context:
space:
mode:
authorAlec Theriault <alec.theriault@gmail.com>2019-01-31 01:37:25 -0800
committerGitHub <noreply@github.com>2019-01-31 01:37:25 -0800
commit1b26460fb3b5df5215cc1e6715661cbc7c950085 (patch)
tree0b5ac6285ecf432021e8365567d48eeb6249f44b /haddock-api/src/Haddock/Interface.hs
parent4c02498a24e6ceb775528bed043b66340296ad06 (diff)
Use `.hie` files for the Hyperlinker backend (#977)
# Summary This is a large architectural change to the Hyperlinker. * extract link (and now also type) information from `.hie` instead of doing ad-hoc SYB traversals of the `RenamedSource`. Also adds a superb type-on-hover feature (#715). * re-engineer the lexer to avoid needless string conversions. By going directly through GHC's `P` monad and taking bytestring slices, we avoid a ton of allocation and have better handling of position pragmas and CPP. In terms of performance, the Haddock side of things has gotten _much_ more efficient. Unfortunately, much of this is cancelled out by the increased GHC workload for generating `.hie` files. For the full set of boot libs (including `ghc`-the-library) * the sum of total time went down by 9-10% overall * the sum of total allocations went down by 6-7% # Motivation Haddock is moving towards working entirely over `.hi` and `.hie` files. This change means we no longer need the `RenamedSource` from `TypecheckedModule` (something which is _not_ in `.hi` files). # Details Along the way a bunch of things were fixed: * Cross package (and other) links are now more reliable (#496) * The lexer tries to recover from errors on every line (instead of at CPP boundaries) * `LINE`/`COLUMN` pragmas are taken into account * filter out zero length tokens before rendering * avoid recomputing the `ModuleName`-based `SrcMap` * remove the last use of `Documentation.Haddock.Utf8` (see #998) * restructure temporary folder logic for `.hi`/`.hie` model
Diffstat (limited to 'haddock-api/src/Haddock/Interface.hs')
-rw-r--r--haddock-api/src/Haddock/Interface.hs55
1 files changed, 10 insertions, 45 deletions
diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs
index 8bfc249c..f1b2d45e 100644
--- a/haddock-api/src/Haddock/Interface.hs
+++ b/haddock-api/src/Haddock/Interface.hs
@@ -43,18 +43,16 @@ import Haddock.Types
import Haddock.Utils
import Control.Monad
+import Control.Exception (evaluate)
import Data.List
import qualified Data.Map as Map
import qualified Data.Set as Set
import Distribution.Verbosity
-import System.Directory
-import System.FilePath
import Text.Printf
import Module (mkModuleSet, emptyModuleSet, unionModuleSet, ModuleSet)
import Digraph
import DynFlags hiding (verbosity)
-import Exception
import GHC hiding (verbosity)
import HscTypes
import FastString (unpackFS)
@@ -90,7 +88,7 @@ processModules verbosity modules flags extIfaces = do
out verbosity verbose "Creating interfaces..."
let instIfaceMap = Map.fromList [ (instMod iface, iface) | ext <- extIfaces
, iface <- ifInstalledIfaces ext ]
- (interfaces, ms) <- createIfaces0 verbosity modules flags instIfaceMap
+ (interfaces, ms) <- createIfaces verbosity modules flags instIfaceMap
let exportedNames =
Set.unions $ map (Set.fromList . ifaceExports) $
@@ -123,39 +121,15 @@ processModules verbosity modules flags extIfaces = do
--------------------------------------------------------------------------------
-createIfaces0 :: Verbosity -> [String] -> [Flag] -> InstIfaceMap -> Ghc ([Interface], ModuleSet)
-createIfaces0 verbosity modules flags instIfaceMap =
- -- Output dir needs to be set before calling depanal since depanal uses it to
- -- compute output file names that are stored in the DynFlags of the
- -- resulting ModSummaries.
- (if useTempDir then withTempOutputDir else id) $ do
- modGraph <- depAnalysis
- createIfaces verbosity flags instIfaceMap modGraph
+createIfaces :: Verbosity -> [String] -> [Flag] -> InstIfaceMap -> Ghc ([Interface], ModuleSet)
+createIfaces verbosity modules flags instIfaceMap = do
+ -- Ask GHC to tell us what the module graph is
+ targets <- mapM (\filePath -> guessTarget filePath Nothing) modules
+ setTargets targets
+ modGraph <- depanal [] False
- where
- useTempDir :: Bool
- useTempDir = Flag_NoTmpCompDir `notElem` flags
-
-
- withTempOutputDir :: Ghc a -> Ghc a
- withTempOutputDir action = do
- tmp <- liftIO getTemporaryDirectory
- x <- liftIO getProcessID
- let dir = tmp </> ".haddock-" ++ show x
- modifySessionDynFlags (setOutputDir dir)
- withTempDir dir action
-
-
- depAnalysis :: Ghc ModuleGraph
- depAnalysis = do
- targets <- mapM (\f -> guessTarget f Nothing) modules
- setTargets targets
- depanal [] False
-
-
-createIfaces :: Verbosity -> [Flag] -> InstIfaceMap -> ModuleGraph -> Ghc ([Interface], ModuleSet)
-createIfaces verbosity flags instIfaceMap mods = do
- let sortedMods = flattenSCCs $ topSortModuleGraph False mods Nothing
+ -- Visit modules in that order
+ let sortedMods = flattenSCCs $ topSortModuleGraph False modGraph Nothing
out verbosity normal "Haddock coverage:"
(ifaces, _, !ms) <- foldM f ([], Map.empty, emptyModuleSet) sortedMods
return (reverse ifaces, ms)
@@ -263,12 +237,3 @@ buildHomeLinks ifaces = foldl upd Map.empty (reverse ifaces)
keep_old env n = Map.insertWith (\_ old -> old) n mdl env
keep_new env n = Map.insert n mdl env
-
---------------------------------------------------------------------------------
--- * Utils
---------------------------------------------------------------------------------
-
-
-withTempDir :: (ExceptionMonad m) => FilePath -> m a -> m a
-withTempDir dir = gbracket_ (liftIO $ createDirectory dir)
- (liftIO $ removeDirectoryRecursive dir)