Skip to content
This repository was archived by the owner on Aug 3, 2024. It is now read-only.

Commit 1b26460

Browse files
authored
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
1 parent 4c02498 commit 1b26460

31 files changed

+9470
-5197
lines changed

CHANGES.md

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,12 @@
66

77
* Support inline markup in markdown-style links (#875)
88

9+
* The hyperlinker backend has been re-engineered to use HIE files
10+
and display type annotations on expressions (#977)
11+
12+
* The hyperlinker backend lexer is now more incremental, faster, and
13+
more memory efficient (#977)
14+
915
## Changes in version 2.22.0
1016

1117
* Make `--package-version` optional for `--hoogle` (#899)

haddock-api/haddock-api.cabal

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -59,6 +59,7 @@ library
5959
, directory
6060
, filepath
6161
, ghc-boot
62+
, ghc-boot-th
6263
, transformers
6364

6465
hs-source-dirs: src
@@ -97,7 +98,6 @@ library
9798
Haddock.Backends.HaddockDB
9899
Haddock.Backends.Hoogle
99100
Haddock.Backends.Hyperlinker
100-
Haddock.Backends.Hyperlinker.Ast
101101
Haddock.Backends.Hyperlinker.Parser
102102
Haddock.Backends.Hyperlinker.Renderer
103103
Haddock.Backends.Hyperlinker.Types
@@ -130,7 +130,6 @@ test-suite spec
130130
Haddock
131131
Haddock.Backends.Hoogle
132132
Haddock.Backends.Hyperlinker
133-
Haddock.Backends.Hyperlinker.Ast
134133
Haddock.Backends.Hyperlinker.Renderer
135134
Haddock.Backends.Hyperlinker.Utils
136135
Haddock.Backends.LaTeX
@@ -187,6 +186,7 @@ test-suite spec
187186
, directory
188187
, filepath
189188
, ghc-boot
189+
, ghc-boot-th
190190
, transformers
191191

192192
build-tool-depends:

haddock-api/resources/html/solarized.css

Lines changed: 42 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -53,3 +53,45 @@ a:link, a:visited {
5353
a:hover, a.hover-highlight {
5454
background-color: #eee8d5;
5555
}
56+
57+
span.annot{
58+
position:relative;
59+
color:#000;
60+
text-decoration:none
61+
}
62+
63+
span.annot:hover{z-index:25; background-color:#ff0}
64+
65+
span.annot span.annottext{
66+
display: none;
67+
border-radius: 5px 5px;
68+
69+
-moz-border-radius: 5px;
70+
-webkit-border-radius: 5px;
71+
72+
box-shadow: 5px 5px 5px rgba(0, 0, 0, 0.1);
73+
-webkit-box-shadow: 5px 5px rgba(0, 0, 0, 0.1);
74+
-moz-box-shadow: 5px 5px rgba(0, 0, 0, 0.1);
75+
76+
position: absolute;
77+
left: 1em; top: 2em;
78+
z-index: 99;
79+
margin-left: 5;
80+
background: #FFFFAA;
81+
border: 2px solid #FFAD33;
82+
padding: 0.8em 1em;
83+
}
84+
85+
span.annot:hover span.annottext{
86+
display:block;
87+
}
88+
89+
/* This bridges the gap so you can mouse into the tooltip without it disappearing */
90+
span.annot span.annottext:before{
91+
content: "";
92+
position: absolute;
93+
left: -1em; top: -1em;
94+
background: #FFFFFF00;
95+
z-index:-1;
96+
padding: 2em 2em;
97+
}

haddock-api/src/Haddock.hs

Lines changed: 39 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,7 @@ import Haddock.Version
3939
import Haddock.InterfaceFile
4040
import Haddock.Options
4141
import Haddock.Utils
42+
import Haddock.GhcUtils (modifySessionDynFlags, setOutputDir)
4243

4344
import Control.Monad hiding (forM_)
4445
import Data.Foldable (forM_, foldl')
@@ -66,6 +67,8 @@ import qualified GHC.Paths as GhcPaths
6667
import Paths_haddock_api (getDataDir)
6768
import System.Directory (doesDirectoryExist)
6869
#endif
70+
import System.Directory (getTemporaryDirectory)
71+
import System.FilePath ((</>))
6972

7073
import Text.ParserCombinators.ReadP (readP_to_S)
7174
import GHC hiding (verbosity)
@@ -164,14 +167,23 @@ haddockWithGhc ghc args = handleTopExceptions $ do
164167
-- bypass the interface version check
165168
let noChecks = Flag_BypassInterfaceVersonCheck `elem` flags
166169

170+
-- Create a temporary directory and redirect GHC output there (unless user
171+
-- requested otherwise).
172+
--
173+
-- Output dir needs to be set before calling 'depanal' since 'depanal' uses it
174+
-- to compute output file names that are stored in the 'DynFlags' of the
175+
-- resulting 'ModSummary's.
176+
let withDir | Flag_NoTmpCompDir `elem` flags = id
177+
| otherwise = withTempOutputDir
178+
167179
unless (Flag_NoWarnings `elem` flags) $ do
168180
hypSrcWarnings flags
169181
forM_ (warnings args) $ \warning -> do
170182
hPutStrLn stderr warning
171183
when noChecks $
172184
hPutStrLn stderr noCheckWarning
173185

174-
ghc flags' $ do
186+
ghc flags' $ withDir $ do
175187
dflags <- getDynFlags
176188

177189
forM_ (optShowInterfaceFile flags) $ \path -> liftIO $ do
@@ -202,6 +214,15 @@ haddockWithGhc ghc args = handleTopExceptions $ do
202214
-- Render even though there are no input files (usually contents/index).
203215
liftIO $ renderStep dflags flags sinceQual qual packages []
204216

217+
-- | Run the GHC action using a temporary output directory
218+
withTempOutputDir :: Ghc a -> Ghc a
219+
withTempOutputDir action = do
220+
tmp <- liftIO getTemporaryDirectory
221+
x <- liftIO getProcessID
222+
let dir = tmp </> ".haddock-" ++ show x
223+
modifySessionDynFlags (setOutputDir dir)
224+
withTempDir dir action
225+
205226
-- | Create warnings about potential misuse of -optghc
206227
warnings :: [String] -> [String]
207228
warnings = map format . filter (isPrefixOf "-optghc")
@@ -221,8 +242,9 @@ withGhc flags action = do
221242
let handleSrcErrors action' = flip handleSourceError action' $ \err -> do
222243
printException err
223244
liftIO exitFailure
245+
needHieFiles = Flag_HyperlinkedSource `elem` flags
224246

225-
withGhc' libDir (ghcFlags flags) (\_ -> handleSrcErrors action)
247+
withGhc' libDir needHieFiles (ghcFlags flags) (\_ -> handleSrcErrors action)
226248

227249

228250
readPackagesAndProcessModules :: [Flag] -> [String]
@@ -444,14 +466,10 @@ readInterfaceFiles name_cache_accessor pairs bypass_version_check = do
444466

445467
-- | Start a GHC session with the -haddock flag set. Also turn off
446468
-- compilation and linking. Then run the given 'Ghc' action.
447-
withGhc' :: String -> [String] -> (DynFlags -> Ghc a) -> IO a
448-
withGhc' libDir flags ghcActs = runGhc (Just libDir) $ do
449-
dynflags <- getSessionDynFlags
450-
dynflags' <- parseGhcFlags (gopt_set dynflags Opt_Haddock) {
451-
hscTarget = HscNothing,
452-
ghcMode = CompManager,
453-
ghcLink = NoLink
454-
}
469+
withGhc' :: String -> Bool -> [String] -> (DynFlags -> Ghc a) -> IO a
470+
withGhc' libDir needHieFiles flags ghcActs = runGhc (Just libDir) $ do
471+
dynflags' <- parseGhcFlags =<< getSessionDynFlags
472+
455473
-- We disable pattern match warnings because than can be very
456474
-- expensive to check
457475
let dynflags'' = unsetPatternMatchWarnings $
@@ -482,11 +500,19 @@ withGhc' libDir flags ghcActs = runGhc (Just libDir) $ do
482500
parseGhcFlags dynflags = do
483501
-- TODO: handle warnings?
484502

485-
let flags' = filterRtsFlags flags
486-
(dynflags', rest, _) <- parseDynamicFlags dynflags (map noLoc flags')
503+
let extra_opts | needHieFiles = [Opt_WriteHie, Opt_Haddock]
504+
| otherwise = [Opt_Haddock]
505+
dynflags' = (foldl' gopt_set dynflags extra_opts)
506+
{ hscTarget = HscNothing
507+
, ghcMode = CompManager
508+
, ghcLink = NoLink
509+
}
510+
flags' = filterRtsFlags flags
511+
512+
(dynflags'', rest, _) <- parseDynamicFlags dynflags' (map noLoc flags')
487513
if not (null rest)
488514
then throwE ("Couldn't parse GHC options: " ++ unwords flags')
489-
else return dynflags'
515+
else return dynflags''
490516

491517
unsetPatternMatchWarnings :: DynFlags -> DynFlags
492518
unsetPatternMatchWarnings dflags =

haddock-api/src/Haddock/Backends/Hyperlinker.hs

Lines changed: 44 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE OverloadedStrings #-}
12
module Haddock.Backends.Hyperlinker
23
( ppHyperlinkedSource
34
, module Haddock.Backends.Hyperlinker.Types
@@ -8,15 +9,24 @@ module Haddock.Backends.Hyperlinker
89
import Haddock.Types
910
import Haddock.Utils (writeUtf8File)
1011
import Haddock.Backends.Hyperlinker.Renderer
12+
import Haddock.Backends.Hyperlinker.Parser
1113
import Haddock.Backends.Hyperlinker.Types
1214
import Haddock.Backends.Hyperlinker.Utils
13-
14-
import Text.XHtml hiding ((</>))
15+
import Haddock.Backends.Xhtml.Utils ( renderToString )
1516

1617
import Data.Maybe
1718
import System.Directory
1819
import System.FilePath
1920

21+
import HieTypes ( HieFile(..), HieASTs(..) )
22+
import HieBin ( readHieFile )
23+
import Data.Map as M
24+
import FastString ( mkFastString )
25+
import Module ( Module, moduleName )
26+
import NameCache ( initNameCache )
27+
import UniqSupply ( mkSplitUniqSupply )
28+
import SysTools.Info ( getCompilerInfo' )
29+
2030

2131
-- | Generate hyperlinked source for given interfaces.
2232
--
@@ -27,10 +37,10 @@ ppHyperlinkedSource :: FilePath -- ^ Output directory
2737
-> FilePath -- ^ Resource directory
2838
-> Maybe FilePath -- ^ Custom CSS file path
2939
-> Bool -- ^ Flag indicating whether to pretty-print HTML
30-
-> SrcMap -- ^ Paths to sources
40+
-> M.Map Module SrcPath -- ^ Paths to sources
3141
-> [Interface] -- ^ Interfaces for which we create source
3242
-> IO ()
33-
ppHyperlinkedSource outdir libdir mstyle pretty srcs ifaces = do
43+
ppHyperlinkedSource outdir libdir mstyle pretty srcs' ifaces = do
3444
createDirectoryIfMissing True srcdir
3545
let cssFile = fromMaybe (defaultCssFile libdir) mstyle
3646
copyFile cssFile $ srcdir </> srcCssFile
@@ -39,17 +49,39 @@ ppHyperlinkedSource outdir libdir mstyle pretty srcs ifaces = do
3949
mapM_ (ppHyperlinkedModuleSource srcdir pretty srcs) ifaces
4050
where
4151
srcdir = outdir </> hypSrcDir
52+
srcs = (srcs', M.mapKeys moduleName srcs')
4253

4354
-- | Generate hyperlinked source for particular interface.
44-
ppHyperlinkedModuleSource :: FilePath -> Bool -> SrcMap -> Interface
45-
-> IO ()
46-
ppHyperlinkedModuleSource srcdir pretty srcs iface =
47-
case ifaceTokenizedSrc iface of
48-
Just tokens -> writeUtf8File path . html . render' $ tokens
49-
Nothing -> return ()
55+
ppHyperlinkedModuleSource :: FilePath -> Bool -> SrcMaps -> Interface -> IO ()
56+
ppHyperlinkedModuleSource srcdir pretty srcs iface = case ifaceHieFile iface of
57+
Just hfp -> do
58+
-- Parse the GHC-produced HIE file
59+
u <- mkSplitUniqSupply 'a'
60+
HieFile { hie_hs_file = file
61+
, hie_asts = HieASTs asts
62+
, hie_types = types
63+
, hie_hs_src = rawSrc
64+
} <- fmap fst (readHieFile (initNameCache u []) hfp)
65+
comp <- getCompilerInfo' df
66+
67+
-- Get the AST and tokens corresponding to the source file we want
68+
let mast | M.size asts == 1 = snd <$> M.lookupMin asts
69+
| otherwise = M.lookup (mkFastString file) asts
70+
tokens = parse comp df file rawSrc
71+
72+
-- Produce and write out the hyperlinked sources
73+
case mast of
74+
Just ast ->
75+
let fullAst = recoverFullIfaceTypes df types ast
76+
in writeUtf8File path . renderToString pretty . render' fullAst $ tokens
77+
Nothing
78+
| M.size asts == 0 -> return ()
79+
| otherwise -> error $ unwords [ "couldn't find ast for"
80+
, file, show (M.keys asts) ]
81+
Nothing -> return ()
5082
where
83+
df = ifaceDynFlags iface
5184
render' = render (Just srcCssFile) (Just highlightScript) srcs
52-
html = if pretty then renderHtml else showHtml
5385
path = srcdir </> hypSrcModuleFile (ifaceMod iface)
5486

5587
-- | Name of CSS file in output directory.
@@ -63,3 +95,4 @@ highlightScript = "highlight.js"
6395
-- | Path to default CSS file.
6496
defaultCssFile :: FilePath -> FilePath
6597
defaultCssFile libdir = libdir </> "html" </> "solarized.css"
98+

0 commit comments

Comments
 (0)