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

Commit 9b403b0

Browse files
committed
DynFlags's unit fields moved to HscEnv
1 parent acf235d commit 9b403b0

File tree

5 files changed

+37
-33
lines changed

5 files changed

+37
-33
lines changed

haddock-api/src/Haddock.hs

Lines changed: 13 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -178,6 +178,7 @@ haddockWithGhc ghc args = handleTopExceptions $ do
178178

179179
ghc flags' $ withDir $ do
180180
dflags <- getDynFlags
181+
unit_state <- hsc_units <$> getSession
181182

182183
forM_ (optShowInterfaceFile flags) $ \path -> liftIO $ do
183184
mIfaceFile <- readInterfaceFiles freshNameCache [(("", Nothing), path)] noChecks
@@ -195,7 +196,7 @@ haddockWithGhc ghc args = handleTopExceptions $ do
195196
}
196197

197198
-- Render the interfaces.
198-
liftIO $ renderStep dflags flags sinceQual qual packages ifaces
199+
liftIO $ renderStep dflags unit_state flags sinceQual qual packages ifaces
199200

200201
else do
201202
when (any (`elem` [Flag_Html, Flag_Hoogle, Flag_LaTeX]) flags) $
@@ -205,7 +206,7 @@ haddockWithGhc ghc args = handleTopExceptions $ do
205206
packages <- liftIO $ readInterfaceFiles freshNameCache (readIfaceArgs flags) noChecks
206207

207208
-- Render even though there are no input files (usually contents/index).
208-
liftIO $ renderStep dflags flags sinceQual qual packages []
209+
liftIO $ renderStep dflags unit_state flags sinceQual qual packages []
209210

210211
-- | Run the GHC action using a temporary output directory
211212
withTempOutputDir :: Ghc a -> Ghc a
@@ -254,9 +255,9 @@ readPackagesAndProcessModules flags files = do
254255
return (packages, ifaces, homeLinks)
255256

256257

257-
renderStep :: DynFlags -> [Flag] -> SinceQual -> QualOption
258+
renderStep :: DynFlags -> UnitState -> [Flag] -> SinceQual -> QualOption
258259
-> [(DocPaths, InterfaceFile)] -> [Interface] -> IO ()
259-
renderStep dflags flags sinceQual nameQual pkgs interfaces = do
260+
renderStep dflags unit_state flags sinceQual nameQual pkgs interfaces = do
260261
updateHTMLXRefs pkgs
261262
let
262263
ifaceFiles = map snd pkgs
@@ -265,12 +266,12 @@ renderStep dflags flags sinceQual nameQual pkgs interfaces = do
265266
((_, Just path), ifile) <- pkgs
266267
iface <- ifInstalledIfaces ifile
267268
return (instMod iface, path)
268-
render dflags flags sinceQual nameQual interfaces installedIfaces extSrcMap
269+
render dflags unit_state flags sinceQual nameQual interfaces installedIfaces extSrcMap
269270

270271
-- | Render the interfaces with whatever backend is specified in the flags.
271-
render :: DynFlags -> [Flag] -> SinceQual -> QualOption -> [Interface]
272+
render :: DynFlags -> UnitState -> [Flag] -> SinceQual -> QualOption -> [Interface]
272273
-> [InstalledInterface] -> Map Module FilePath -> IO ()
273-
render dflags flags sinceQual qual ifaces installedIfaces extSrcMap = do
274+
render dflags unit_state flags sinceQual qual ifaces installedIfaces extSrcMap = do
274275

275276
let
276277
title = fromMaybe "" (optTitle flags)
@@ -283,7 +284,6 @@ render dflags flags sinceQual qual ifaces installedIfaces extSrcMap = do
283284
opt_latex_style = optLaTeXStyle flags
284285
opt_source_css = optSourceCssFile flags
285286
opt_mathjax = optMathjax flags
286-
pkgs = unitState dflags
287287
dflags'
288288
| unicode = gopt_set dflags Opt_PrintUnicodeSyntax
289289
| otherwise = dflags
@@ -297,7 +297,7 @@ render dflags flags sinceQual qual ifaces installedIfaces extSrcMap = do
297297
pkgMod = fmap ifaceMod (listToMaybe ifaces)
298298
pkgKey = fmap moduleUnit pkgMod
299299
pkgStr = fmap unitString pkgKey
300-
pkgNameVer = modulePackageInfo dflags flags pkgMod
300+
pkgNameVer = modulePackageInfo unit_state flags pkgMod
301301
pkgName = fmap (unpackFS . (\(PackageName n) -> n)) (fst pkgNameVer)
302302
sincePkg = case sinceQual of
303303
External -> pkgName
@@ -342,7 +342,7 @@ render dflags flags sinceQual qual ifaces installedIfaces extSrcMap = do
342342
-- records the *wired in* identity base. So untranslate it
343343
-- so that we can service the request.
344344
unwire :: Module -> Module
345-
unwire m = m { moduleUnit = unwireUnit (unitState dflags) (moduleUnit m) }
345+
unwire m = m { moduleUnit = unwireUnit unit_state (moduleUnit m) }
346346

347347
reexportedIfaces <- concat `fmap` (for (reexportFlags flags) $ \mod_str -> do
348348
let warn = hPutStrLn stderr . ("Warning: " ++)
@@ -373,7 +373,7 @@ render dflags flags sinceQual qual ifaces installedIfaces extSrcMap = do
373373
when (Flag_GenContents `elem` flags) $ do
374374
withTiming dflags' "ppHtmlContents" (const ()) $ do
375375
_ <- {-# SCC ppHtmlContents #-}
376-
ppHtmlContents pkgs odir title pkgStr
376+
ppHtmlContents unit_state odir title pkgStr
377377
themes opt_mathjax opt_index_url sourceUrls' opt_wiki_urls
378378
allVisibleIfaces True prologue pretty
379379
sincePkg (makeContentsQual qual)
@@ -383,7 +383,7 @@ render dflags flags sinceQual qual ifaces installedIfaces extSrcMap = do
383383
when (Flag_Html `elem` flags) $ do
384384
withTiming dflags' "ppHtml" (const ()) $ do
385385
_ <- {-# SCC ppHtml #-}
386-
ppHtml pkgs title pkgStr visibleIfaces reexportedIfaces odir
386+
ppHtml unit_state title pkgStr visibleIfaces reexportedIfaces odir
387387
prologue
388388
themes opt_mathjax sourceUrls' opt_wiki_urls
389389
opt_contents_url opt_index_url unicode sincePkg qual
@@ -403,7 +403,7 @@ render dflags flags sinceQual qual ifaces installedIfaces extSrcMap = do
403403

404404
pkgVer =
405405
fromMaybe (makeVersion []) mpkgVer
406-
in ppHoogle dflags' pkgNameStr pkgVer title (fmap _doc prologue)
406+
in ppHoogle dflags' unit_state pkgNameStr pkgVer title (fmap _doc prologue)
407407
visibleIfaces odir
408408
_ -> putStrLn . unlines $
409409
[ "haddock: Unable to find a package providing module "

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

Lines changed: 10 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,7 @@ import GHC.Driver.Ppr
3131
import GHC.Utils.Outputable as Outputable
3232
import GHC.Utils.Panic
3333
import GHC.Parser.Annotation (IsUnicodeSyntax(..))
34+
import GHC.Unit.State
3435

3536
import Data.Char
3637
import Data.List
@@ -46,8 +47,8 @@ prefix = ["-- Hoogle documentation, generated by Haddock"
4647
,""]
4748

4849

49-
ppHoogle :: DynFlags -> String -> Version -> String -> Maybe (Doc RdrName) -> [Interface] -> FilePath -> IO ()
50-
ppHoogle dflags package version synopsis prologue ifaces odir = do
50+
ppHoogle :: DynFlags -> UnitState -> String -> Version -> String -> Maybe (Doc RdrName) -> [Interface] -> FilePath -> IO ()
51+
ppHoogle dflags unit_state package version synopsis prologue ifaces odir = do
5152
let -- Since Hoogle is line based, we want to avoid breaking long lines.
5253
dflags' = dflags{ pprCols = maxBound }
5354
filename = package ++ ".txt"
@@ -56,16 +57,16 @@ ppHoogle dflags package version synopsis prologue ifaces odir = do
5657
["@package " ++ package] ++
5758
["@version " ++ showVersion version
5859
| not (null (versionBranch version)) ] ++
59-
concat [ppModule dflags' i | i <- ifaces, OptHide `notElem` ifaceOptions i]
60+
concat [ppModule dflags' unit_state i | i <- ifaces, OptHide `notElem` ifaceOptions i]
6061
createDirectoryIfMissing True odir
6162
writeUtf8File (odir </> filename) (unlines contents)
6263

63-
ppModule :: DynFlags -> Interface -> [String]
64-
ppModule dflags iface =
64+
ppModule :: DynFlags -> UnitState -> Interface -> [String]
65+
ppModule dflags unit_state iface =
6566
"" : ppDocumentation dflags (ifaceDoc iface) ++
6667
["module " ++ moduleString (ifaceMod iface)] ++
6768
concatMap (ppExport dflags) (ifaceExportItems iface) ++
68-
concatMap (ppInstance dflags) (ifaceInstances iface)
69+
concatMap (ppInstance dflags unit_state) (ifaceInstances iface)
6970

7071

7172
---------------------------------------------------------------------
@@ -204,9 +205,9 @@ ppFam dflags decl@(FamilyDecl { fdInfo = info })
204205
ClosedTypeFamily{} -> decl { fdInfo = OpenTypeFamily }
205206
_ -> decl
206207

207-
ppInstance :: DynFlags -> ClsInst -> [String]
208-
ppInstance dflags x =
209-
[dropComment $ outWith (showSDocForUser dflags alwaysQualify) cls]
208+
ppInstance :: DynFlags -> UnitState -> ClsInst -> [String]
209+
ppInstance dflags unit_state x =
210+
[dropComment $ outWith (showSDocForUser dflags unit_state alwaysQualify) cls]
210211
where
211212
-- As per #168, we don't want safety information about the class
212213
-- in Hoogle output. The easiest way to achieve this is to set the

haddock-api/src/Haddock/Interface.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -159,18 +159,19 @@ processModule verbosity modsum flags modMap instIfaceMap = do
159159
IsBoot ->
160160
return Nothing
161161
NotBoot -> do
162+
unit_state <- hsc_units <$> getSession
162163
out verbosity verbose "Creating interface..."
163164
(interface, msgs) <- {-# SCC createIterface #-}
164165
withTimingD "createInterface" (const ()) $ do
165-
runWriterGhc $ createInterface tm flags modMap instIfaceMap
166+
runWriterGhc $ createInterface tm unit_state flags modMap instIfaceMap
166167

167168
-- We need to keep track of which modules were somehow in scope so that when
168169
-- Haddock later looks for instances, it also looks in these modules too.
169170
--
170171
-- See https://github.com/haskell/haddock/issues/469.
171172
hsc_env <- getSession
172173
let new_rdr_env = tcg_rdr_env . fst . GHC.tm_internals_ $ tm
173-
home_unit = mkHomeUnitFromFlags (hsc_dflags hsc_env)
174+
home_unit = hsc_home_unit hsc_env
174175
!mods = mkModuleSet [ nameModule name
175176
| gre <- globalRdrEnvElts new_rdr_env
176177
, let name = gre_name gre

haddock-api/src/Haddock/Interface/Create.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,7 @@ import GHC.Types.SourceFile
4747
import GHC.Core.ConLike (ConLike(..))
4848
import GHC
4949
import GHC.Driver.Ppr
50+
import GHC.Driver.Env
5051
import GHC.Types.Name
5152
import GHC.Types.Name.Set
5253
import GHC.Types.Name.Env
@@ -67,11 +68,12 @@ import GHC.Unit.Module.Warnings
6768
-- To do this, we need access to already processed modules in the topological
6869
-- sort. That's what's in the 'IfaceMap'.
6970
createInterface :: TypecheckedModule
71+
-> UnitState
7072
-> [Flag] -- Boolean flags
7173
-> IfaceMap -- Locally processed modules
7274
-> InstIfaceMap -- External, already installed interfaces
7375
-> ErrMsgGhc Interface
74-
createInterface tm flags modMap instIfaceMap = do
76+
createInterface tm unit_state flags modMap instIfaceMap = do
7577

7678
let ms = pm_mod_summary . tm_parsed_module $ tm
7779
mi = moduleInfo tm
@@ -84,7 +86,7 @@ createInterface tm flags modMap instIfaceMap = do
8486
!instances = modInfoInstances mi
8587
!fam_instances = md_fam_insts md
8688
!exportedNames = modInfoExportsWithSelectors mi
87-
(pkgNameFS, _) = modulePackageInfo dflags flags (Just mdl)
89+
(pkgNameFS, _) = modulePackageInfo unit_state flags (Just mdl)
8890
pkgName = fmap (unpackFS . (\(PackageName n) -> n)) pkgNameFS
8991

9092
(TcGblEnv { tcg_rdr_env = gre
@@ -164,8 +166,7 @@ createInterface tm flags modMap instIfaceMap = do
164166
| otherwise = exportItems
165167
!prunedExportItems = seqList prunedExportItems' `seq` prunedExportItems'
166168

167-
let !aliases =
168-
mkAliasMap (unitState dflags) $ tm_renamed_source tm
169+
let !aliases = mkAliasMap unit_state $ tm_renamed_source tm
169170

170171
modWarn <- liftErrMsg (moduleWarning dflags gre warnings)
171172

haddock-api/src/Haddock/Options.hs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,8 @@ import Data.Version
4545
import Control.Applicative
4646
import Distribution.Verbosity
4747
import GHC.Data.FastString
48-
import GHC ( DynFlags, Module, moduleUnit, unitState )
48+
import GHC ( DynFlags, Module, moduleUnit )
49+
import GHC.Unit.State
4950
import Haddock.Types
5051
import Haddock.Utils
5152
import GHC.Unit.State
@@ -370,16 +371,16 @@ optLast xs = Just (last xs)
370371
--
371372
-- The @--package-name@ and @--package-version@ Haddock flags allow the user to
372373
-- specify this information manually and it is returned here if present.
373-
modulePackageInfo :: DynFlags
374+
modulePackageInfo :: UnitState
374375
-> [Flag] -- ^ Haddock flags are checked as they may contain
375376
-- the package name or version provided by the user
376377
-- which we prioritise
377378
-> Maybe Module
378379
-> (Maybe PackageName, Maybe Data.Version.Version)
379-
modulePackageInfo _dflags _flags Nothing = (Nothing, Nothing)
380-
modulePackageInfo dflags flags (Just modu) =
380+
modulePackageInfo _unit_state _flags Nothing = (Nothing, Nothing)
381+
modulePackageInfo unit_state flags (Just modu) =
381382
( optPackageName flags <|> fmap unitPackageName pkgDb
382383
, optPackageVersion flags <|> fmap unitPackageVersion pkgDb
383384
)
384385
where
385-
pkgDb = lookupUnit (unitState dflags) (moduleUnit modu)
386+
pkgDb = lookupUnit unit_state (moduleUnit modu)

0 commit comments

Comments
 (0)