[Git][ghc/ghc][master] Haddock: Add no-compilation flag

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Sep 3 17:15:28 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
1499764f by Sjoerd Visscher at 2024-08-29T16:52:56+02:00
Haddock: Add no-compilation flag

This flag makes sure to avoid recompilation of the code when generating documentation by only reading the .hi and .hie files, and throw an error if it can't find them.

- - - - -


9 changed files:

- utils/haddock/.gitignore
- utils/haddock/CHANGES.md
- utils/haddock/doc/invoking.rst
- utils/haddock/haddock-api/src/Haddock.hs
- utils/haddock/haddock-api/src/Haddock/Interface.hs
- utils/haddock/haddock-api/src/Haddock/Options.hs
- utils/haddock/haddock-test/src/Test/Haddock.hs
- utils/haddock/haddock-test/src/Test/Haddock/Config.hs
- utils/haddock/latex-test/Main.hs


Changes:

=====================================
utils/haddock/.gitignore
=====================================
@@ -11,6 +11,10 @@
 /hypsrc-test/one-shot-out/
 /latex-test/one-shot-out/
 /hoogle-test/one-shot-out/
+/html-test/no-compilation-out/
+/hypsrc-test/no-compilation-out/
+/latex-test/no-compilation-out/
+/hoogle-test/no-compilation-out/
 
 *.o
 *.hi


=====================================
utils/haddock/CHANGES.md
=====================================
@@ -3,6 +3,10 @@
 
  * Add incremental mode to support rendering documentation one module at a time.
 
+ * The flag `--no-compilation` has been added. This flag causes Haddock to avoid
+   recompilation of the code when generating documentation by only reading
+   the `.hi` and `.hie` files, and will throw an error if it can't find them.
+
  * Fix large margin on top of small headings
 
  * Include `package_info` with haddock's `--show-interface` option.


=====================================
utils/haddock/doc/invoking.rst
=====================================
@@ -542,6 +542,13 @@ The following options are available:
     ``cabal`` uses temporary `response files
     <https://gcc.gnu.org/wiki/Response_Files>`_ to pass arguments to Haddock.
 
+.. option:: --no-compilation
+
+    Always :ref:`avoids recompilation<avoiding-recompilation>`, only loads the
+    required ``.hi`` and ``.hie`` files. Haddock will throw an error when it can't
+    find them. This will not check if the input files are out of date.
+    (This flag implies :option:`--no-tmp-comp-dir`.)
+
 .. option:: --incremental=<module>
 
     Use Haddock in :ref:`incremental mode<incremental-mode>`. Haddock will generate
@@ -555,6 +562,8 @@ sources are accepted without the need for the user to do anything. To
 use the C pre-processor, however, the user must pass the ``-cpp``
 option to GHC using :option:`--optghc`.
 
+.. _avoiding-recompilation:
+
 Avoiding recompilation
 ----------------------
 
@@ -579,32 +588,15 @@ should write the ``.hi`` and ``.hie`` files by providing the
 are building your application with ``cabal build``, the default location is in
 ``dist-newstyle/build/<arch>-<os>/ghc-<ghc-version>/<component>-0.1.0/build``.
 
-The next step is to ensure that the flags which Haddock passes to GHC will not
-trigger recompilation. Unfortunately, this is not very easy to do if you are
-invoking Haddock through ``cabal haddock``. Upon ``cabal haddock``, Cabal passes
-a ``--optghc="-optP-D__HADDOCK_VERSION__=NNNN"`` (where ``NNNN`` is the Haddock
-version number) flag to Haddock, which forwards the ``-optP=...`` flag to GHC
-and triggers a recompilation (unless the existing build results were also
-created by a ``cabal haddock``). Additionally, Cabal passes a
-``--optghc="-stubdir=<temp directory>"`` flag to Haddock, which forwards the
-``-stubdir=<temp directory>`` flag to GHC and triggers a recompilation since
-``-stubdir`` adds a global include directory. Moreover, since the ``stubdir``
-that Cabal passes is a temporary directory, a recompilation is triggered even
-for immediately successive invocations. To avoid recompilations due to these
-flags, one must manually extract the arguments passed to Haddock by Cabal and
-remove the ``--optghc="-optP-D__HADDOCK_VERSION__=NNNN"`` and
-``--optghc="-stubdir=<temp directory>"`` flags. This can be achieved using the
-:option:`--trace-args` flag by invoking ``cabal haddock`` with
-``--haddock-option="--trace-args"`` and copying the traced arguments to a script
-which makes an equivalent call to Haddock without the aformentioned flags.
-
-In addition to the above, Cabal passes a temporary directory as ``-hidir`` to
-Haddock by default. Obviously, this also triggers a recompilation for every
-invocation of ``cabal haddock``, since it will never find the necessary
+The next step is to make sure Haddock runs in no-compilation mode by using
+the :option:`--no-compilation` flag. In addition, Cabal passes a
+temporary directory as ``-hidir`` to Haddock by default. This will cause
+``cabal haddock`` to error, since it will never find the necessary
 interface files in that temporary directory. To remedy this, pass a
 ``--optghc="-hidir=/path/to/hidir"`` flag to Haddock, where ``/path/to/hidir``
 is the path to the directory in which your build process is writing ``.hi``
-files.
+files. You can do this by invoking ``cabal haddock`` with
+``--haddock-options="--no-compilation --optghc=-hidir --optghc=/path/to/hidir"``.
 
 Following the steps above will allow you to take full advantage of "hi-haddock"
 and generate Haddock documentation from existing build results without requiring


=====================================
utils/haddock/haddock-api/src/Haddock.hs
=====================================
@@ -166,14 +166,14 @@ haddockWithGhc ghc args = handleTopExceptions $ do
   qual <- rightOrThrowE (qualification flags)
   sinceQual <- rightOrThrowE (sinceQualification flags)
 
-  let isOneShotMode = isJust (optOneShot flags)
+  let noCompilation = isJust (optOneShot flags) || Flag_NoCompilation `elem` flags
 
   -- Inject dynamic-too into ghc options if the ghc we are using was built with
-  -- dynamic linking (except when in one-shot mode)
+  -- dynamic linking (except when not doing any compilation)
   flags'' <- ghc flags $ do
         df <- getDynFlags
         case lookup "GHC Dynamic" (compilerInfo df) of
-          Just "YES" | not isOneShotMode -> return $ Flag_OptGhc "-dynamic-too" : flags
+          Just "YES" | not noCompilation -> return $ Flag_OptGhc "-dynamic-too" : flags
           _ -> return flags
 
   -- Inject `-j` into ghc options, if given to Haddock
@@ -191,8 +191,7 @@ haddockWithGhc ghc args = handleTopExceptions $ do
   -- 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 'ModSummary's.
-  let withDir | Flag_NoTmpCompDir `elem` flags = id
-              | isOneShotMode = id
+  let withDir | Flag_NoTmpCompDir `elem` flags || noCompilation = id
               | otherwise = withTempOutputDir
 
   -- Output warnings about potential misuse of some flags


=====================================
utils/haddock/haddock-api/src/Haddock/Interface.hs
=====================================
@@ -176,19 +176,21 @@ createIfaces verbosity modules flags instIfaceMap = do
   dflags <- getSessionDynFlags
   let dflags' = dflags { ldInputs = map (FileOption "") o_files
                                     ++ ldInputs dflags }
-  _ <- setSessionDynFlags dflags'
+      dflags'' = if Flag_NoCompilation `elem` flags then dflags' { ghcMode = OneShot } else dflags'
+  _ <- setSessionDynFlags dflags''
   targets <- mapM (\(filePath, _) -> guessTarget filePath Nothing Nothing) hs_srcs
   setTargets targets
   (_errs, modGraph) <- depanalE [] False
 
-  liftIO $ traceMarkerIO "Load started"
-  -- Create (if necessary) and load .hi-files.
-  success <- withTimingM "load'" (const ()) $
-               load' noIfaceCache LoadAllTargets mkUnknownDiagnostic (Just batchMsg) modGraph
-  when (failed success) $ do
-    out verbosity normal "load' failed"
-    liftIO exitFailure
-  liftIO $ traceMarkerIO "Load ended"
+  -- Create (if necessary) and load .hi-files. With --no-compilation this happens later.
+  when (Flag_NoCompilation `notElem` flags) $ do
+    liftIO $ traceMarkerIO "Load started"
+    success <- withTimingM "load'" (const ()) $
+                load' noIfaceCache LoadAllTargets mkUnknownDiagnostic (Just batchMsg) modGraph
+    when (failed success) $ do
+      out verbosity normal "load' failed"
+      liftIO exitFailure
+    liftIO $ traceMarkerIO "Load ended"
 
       -- We topologically sort the module graph including boot files,
       -- so it should be acylic (hopefully we failed much earlier if this is not the case)
@@ -260,6 +262,20 @@ dropErr :: MaybeErr e a -> Maybe a
 dropErr (Succeeded a) = Just a
 dropErr (Failed _) = Nothing
 
+loadHiFile :: HscEnv -> Outputable.SDoc -> Module -> IO (ModIface, ([ClsInst], [FamInst]))
+loadHiFile hsc_env doc theModule = initIfaceLoad hsc_env $ do
+
+  mod_iface <- loadSysInterface doc theModule
+
+  insts <- initIfaceLcl (mi_semantic_module mod_iface) doc (mi_boot mod_iface) $ do
+
+    new_eps_insts     <- mapM tcIfaceInst (mi_insts mod_iface)
+    new_eps_fam_insts <- mapM tcIfaceFamInst (mi_fam_insts mod_iface)
+
+    pure (new_eps_insts, new_eps_fam_insts)
+
+  pure (mod_iface, insts)
+
 processModule :: Verbosity -> ModSummary -> [Flag] -> IfaceMap -> InstIfaceMap -> WarningMap -> Ghc (Maybe Interface)
 processModule verbosity modSummary flags ifaceMap instIfaceMap warningMap = do
   out verbosity verbose $ "Checking module " ++ moduleString (ms_mod modSummary) ++ "..."
@@ -267,17 +283,19 @@ processModule verbosity modSummary flags ifaceMap instIfaceMap warningMap = do
   hsc_env <- getSession
   dflags <- getDynFlags
   let sDocContext = DynFlags.initSDocContext dflags Outputable.defaultUserStyle
-  let hmi = case lookupHpt (hsc_HPT hsc_env) (moduleName $ ms_mod modSummary) of
-        Nothing -> error "processModule: All modules should be loaded into the HPT by this point"
-        Just x -> x
-      mod_iface = hm_iface hmi
+      doc = text "processModule"
       unit_state = hsc_units hsc_env
 
-      cls_insts = instEnvElts . md_insts $ hm_details hmi
+  (mod_iface, insts) <- if Flag_NoCompilation `elem` flags
+    then liftIO $ loadHiFile hsc_env doc $ ms_mod modSummary
+    else
+      let hmi = case lookupHpt (hsc_HPT hsc_env) (moduleName $ ms_mod modSummary) of
+            Nothing -> error "processModule: All modules should be loaded into the HPT by this point"
+            Just x -> x
+          cls_insts = instEnvElts . md_insts $ hm_details hmi
+          fam_insts = md_fam_insts $ hm_details hmi
 
-      fam_insts = md_fam_insts $ hm_details hmi
-
-      insts = (cls_insts, fam_insts)
+      in pure (hm_iface hmi, (cls_insts, fam_insts))
 
   !interface <- do
     logger <- getLogger
@@ -363,18 +381,7 @@ createOneShotIface verbosity flags instIfaceMap moduleNameStr = do
   modifySession $ hscSetFlags dflags
   hsc_env <- getSession
 
-  (iface, insts) <- liftIO $ initIfaceLoad hsc_env $ do
-
-    iface <- loadSysInterface doc $ mkMainModule_ moduleNm
-
-    insts <- initIfaceLcl (mi_semantic_module iface) doc (mi_boot iface) $ do
-
-      new_eps_insts     <- mapM tcIfaceInst (mi_insts iface)
-      new_eps_fam_insts <- mapM tcIfaceFamInst (mi_fam_insts iface)
-
-      pure (new_eps_insts, new_eps_fam_insts)
-
-    pure (iface, insts)
+  (iface, insts) <- liftIO $ loadHiFile hsc_env doc $ mkMainModule_ moduleNm
 
   -- Update the DynFlags with the extensions from the source file (as stored in the interface file)
   -- This is instead of ms_hspp_opts from ModSummary, which is not available in one-shot mode.


=====================================
utils/haddock/haddock-api/src/Haddock/Options.hs
=====================================
@@ -124,6 +124,7 @@ data Flag
   | Flag_ParCount (Maybe Int)
   | Flag_TraceArgs
   | Flag_OneShot String
+  | Flag_NoCompilation
   deriving (Eq, Show)
 
 options :: Bool -> [OptDescr Flag]
@@ -158,6 +159,11 @@ options backwardsCompat =
       ["show-interface"]
       (ReqArg Flag_ShowInterface "FILE")
       "print the interface in a human readable form"
+  , Option
+      []
+      ["no-compilation"]
+      (NoArg Flag_NoCompilation)
+      "never compile the code, just read the .hi files"
   , Option
       []
       ["incremental"]


=====================================
utils/haddock/haddock-test/src/Test/Haddock.hs
=====================================
@@ -10,6 +10,7 @@ module Test.Haddock
 import Control.Monad
 import qualified Data.ByteString.Char8 as BS
 import qualified Data.Map.Strict as Map
+import Data.Foldable (for_)
 import Data.Maybe
 import GHC.ResponseFile
 import System.Directory
@@ -74,6 +75,7 @@ maybeDiff cfg@(Config{cfgDiffTool = (Just diff)}) files = do
 runHaddock :: Config c -> IO Bool
 runHaddock cfg@(Config{..}) = do
   createEmptyDirectory $ cfgOutDir cfg
+  createEmptyDirectory $ cfgNoCompilationOutDir cfg
   createEmptyDirectory $ cfgOneShotOutDir cfg
 
   putStrLn "Generating documentation..."
@@ -93,41 +95,65 @@ runHaddock cfg@(Config{..}) = do
     succeeded <- waitForSuccess msg stdout =<< runProcess' cfgHaddockPath pc
     unless succeeded $ removeDirectoryRecursive (outDir cfgDirConfig tpkg)
 
-    if cfgSkipOneShot then pure succeeded else do
-      let oneShotDir = oneshotOutDir cfgDirConfig tpkg
-          hiDir = oneShotDir </> "hi"
-          hieDir = oneShotDir </> "hie"
+    let noCompilationDir = noCompilationOutDir cfgDirConfig tpkg
+        hiDir = noCompilationDir </> "hi"
+        hieDir = noCompilationDir </> "hie"
+
+    createEmptyDirectory noCompilationDir
+    createEmptyDirectory hiDir
+    createEmptyDirectory hieDir
+
+    -- Build .hi files
+    let pc =
+          processConfig
+            { pcArgs =
+                concat
+                  [
+                    [ "--make"
+                    , "-haddock"
+                    , "-fwrite-interface"
+                    , "-fwrite-ide-info"
+                    , "-no-keep-o-files"
+                    , "-hidir=" ++ hiDir
+                    , "-hiedir=" ++ hieDir
+                    ]
+                  , tpkgFiles tpkg
+                  ]
+            , pcEnv = Just cfgEnv
+            }
+    let msg = "Failed to run GHC on test package '" ++ tpkgName tpkg ++ "'"
+    _ <- waitForSuccess msg stdout =<< runProcess' cfgGhcPath pc
+
+    -- Generate documentation with no-compilation flag
+    let pc =
+          processConfig
+            { pcArgs =
+                concat
+                  [ cfgHaddockArgs
+                  , [ "--odir=" ++ noCompilationDir
+                    , "--optghc=-hidir=" ++ hiDir
+                    , "--optghc=-hiedir=" ++ hieDir
+                    , "--no-compilation"
+                    ]
+                  , tpkgFiles tpkg
+                  ]
+            , pcEnv = Just cfgEnv
+            }
+
+    let msg = "Failed to run Haddock in no-compilation mode on test package '" ++ tpkgName tpkg ++ "'"
+    succeededNC <- waitForSuccess msg stdout =<< runProcess' cfgHaddockPath pc
+
+    -- Generate documentation incrementally
+    if cfgSkipOneShot then pure (succeeded && succeededNC) else do
+      let oneShotDir = oneShotOutDir cfgDirConfig tpkg
           responseFile = hiDir </> "response-file"
       createEmptyDirectory oneShotDir
-      createEmptyDirectory hiDir
-      createEmptyDirectory hieDir
       writeFile responseFile $ escapeArgs
         [ "--odir=" ++ oneShotDir
         , "--optghc=-hidir=" ++ hiDir
         , "--optghc=-hiedir=" ++ hieDir
         ]
 
-      -- Build .hi files
-      let pc' =
-            processConfig
-              { pcArgs =
-                  concat
-                    [
-                      [ "--make"
-                      , "-haddock"
-                      , "-fwrite-interface"
-                      , "-fwrite-ide-info"
-                      , "-no-keep-o-files"
-                      , "-hidir=" ++ hiDir
-                      , "-hiedir=" ++ hieDir
-                      ]
-                    , tpkgFiles tpkg
-                    ]
-              , pcEnv = Just cfgEnv
-              }
-      let msg = "Failed to run GHC on test package '" ++ tpkgName tpkg ++ "'"
-      _ <- waitForSuccess msg stdout =<< runProcess' cfgGhcPath pc'
-
       files <- filter ((== ".hi") . takeExtension) <$> listDirectory hiDir
       -- Use the output order of GHC as a simple dependency order
       filesSorted <- Map.elems . Map.fromList <$> traverse (\file -> (,file) <$> getModificationTime (hiDir </> file)) files
@@ -157,37 +183,30 @@ runHaddock cfg@(Config{..}) = do
                   escapeArgs [ "--read-interface=" ++ srcRef ++ haddockFile ]
                 loop files
               else pure False
-      succeeded2 <- loop filesSorted
-      when succeeded2 $ do
+      succeededOS <- loop filesSorted
+      when (succeededNC && succeededOS) $ do
         removeDirectoryRecursive hiDir
         removeDirectoryRecursive hieDir
-      pure succeeded2
+      pure (succeeded && succeededNC && succeededOS)
 
   let somethingFailed = any not successes
   pure somethingFailed
 
 checkFile :: Config c -> FilePath -> IO CheckResult
 checkFile cfg file = do
-  hasRef <- doesFileExist $ refFile dcfg file
-  if hasRef
-    then do
-      mout <- readOut cfg file
-      mref <- readRef cfg file
-      case (mout, mref) of
-        (Just out, Just ref)
-          | ccfgEqual ccfg out ref ->
-              if cfgSkipOneShot cfg || dcfgCheckIgnoreOneShot (cfgDirConfig cfg) file
-                then return Pass
-                else do
-                  mOneShotOut <- readOneShotOut cfg file
-                  return $ case mOneShotOut of
-                    Just oneShotOut
-                      | ccfgEqual ccfg oneShotOut out -> Pass
-                      | otherwise -> Fail
-                    Nothing -> Error "Failed to parse one-shot input file"
-          | otherwise -> return Fail
-        _ -> return $ Error "Failed to parse input files"
-    else return NoRef
+  mref <- readRef cfg file
+  case mref of
+    Just ref -> do
+      let checkStep dcfgDir = ccfgEqual ccfg ref <$> readOut cfg dcfgDir file
+      result <- checkStep dcfgOutDir
+      resultNC <- if dcfgCheckIgnoreNoCompilation (cfgDirConfig cfg) file
+        then pure True
+        else checkStep dcfgNoCompilationOutDir
+      resultOS <- if cfgSkipOneShot cfg || dcfgCheckIgnoreOneShot (cfgDirConfig cfg) file
+        then pure True
+        else checkStep dcfgOneShotOutDir
+      pure $ if and [result, resultNC, resultOS] then Pass else Fail
+    Nothing -> return NoRef
   where
     ccfg = cfgCheckConfig cfg
     dcfg = cfgDirConfig cfg
@@ -207,59 +226,50 @@ readRef cfg file =
     dcfg = cfgDirConfig cfg
 
 -- | Read (and clean) the test output artifact for a test
-readOut :: Config c -> FilePath -> IO (Maybe c)
-readOut cfg file =
-  fmap (ccfgClean ccfg file) . ccfgRead ccfg . BS.unpack
-    <$> BS.readFile (outFile dcfg file)
-  where
-    ccfg = cfgCheckConfig cfg
-    dcfg = cfgDirConfig cfg
-
-readOneShotOut :: Config c -> FilePath -> IO (Maybe c)
-readOneShotOut cfg file =
-  fmap (ccfgClean ccfg file) . ccfgRead ccfg . BS.unpack
-    <$> BS.readFile (oneShotOutFile dcfg file)
+readOut :: Config c -> (DirConfig -> FilePath) -> FilePath -> IO c
+readOut cfg dcfgDir file = do
+  res <- fmap (ccfgClean ccfg file) . ccfgRead ccfg . BS.unpack
+    <$> BS.readFile outFile
+  case res of
+    Just out -> return out
+    Nothing -> error $ "Failed to parse output file: " ++ outFile
   where
     ccfg = cfgCheckConfig cfg
     dcfg = cfgDirConfig cfg
+    outFile = dcfgDir dcfg </> file
 
 diffFile :: Config c -> FilePath -> FilePath -> IO ()
 diffFile cfg diff file = do
-  Just out <- readOut cfg file
-  Just oneShotOut <- readOneShotOut cfg file
   Just ref <- readRef cfg file
-  writeFile outFile' $ ccfgDump ccfg out
-  writeFile oneShotOutFile' $ ccfgDump ccfg oneShotOut
-  writeFile refFile' $ ccfgDump ccfg ref
-
-  putStrLn $ "Diff for file \"" ++ file ++ "\":"
-  hFlush stdout
-  handle <-
-    runProcess' diff $
-      processConfig
-        { pcArgs = [outFile', refFile']
-        , pcStdOut = Just stdout
-        }
-  void $ waitForProcess handle
-  handle' <-
-    runProcess' diff $
-      processConfig
-        { pcArgs = [oneShotOutFile', outFile']
-        , pcStdOut = Just stdout
-        }
-  void $ waitForProcess handle'
-  return ()
+  out <- readOut cfg dcfgOutDir file
+  noCompilationOut <- readOut cfg dcfgNoCompilationOutDir file
+  oneShotOut <- readOut cfg dcfgOneShotOutDir file
+  writeFile (dumpFile "ref") $ ccfgDump ccfg ref
+  writeFile (dumpFile "out") $ ccfgDump ccfg out
+  writeFile (dumpFile "oneShot") $ ccfgDump ccfg oneShotOut
+  writeFile (dumpFile "noCompilation") $ ccfgDump ccfg oneShotOut
+
+  for_ ["out", "oneShot", "noCompilation"] $ \nm -> do
+    let outFile = dumpFile nm
+        refFile = dumpFile "ref"
+    putStrLn $ "Diff for file \"" ++ outFile ++ "\":"
+    hFlush stdout
+    handle <-
+      runProcess' diff $
+        processConfig
+          { pcArgs = [outFile, refFile]
+          , pcStdOut = Just stdout
+          }
+    void $ waitForProcess handle
   where
     dcfg = cfgDirConfig cfg
     ccfg = cfgCheckConfig cfg
-    outFile' = outFile dcfg file <.> "dump"
-    oneShotOutFile' = oneShotOutFile dcfg file <.> "dump"
-    refFile' = outFile dcfg file <.> "ref" <.> "dump"
+    dumpFile nm = dcfgOutDir dcfg </> file <.> nm <.> "dump"
 
 maybeAcceptFile :: Config c -> FilePath -> CheckResult -> IO CheckResult
 maybeAcceptFile cfg file result
   | cfgAccept cfg && result `elem` [NoRef, Fail] = do
-      Just out <- readOut cfg file
+      out <- readOut cfg dcfgOutDir file
       let ref = refFile dcfg file
       createDirectoryIfMissing True (takeDirectory ref)
       writeFile ref $ ccfgDump ccfg out
@@ -272,14 +282,11 @@ maybeAcceptFile _ _ result = pure result
 outDir :: DirConfig -> TestPackage -> FilePath
 outDir dcfg tpkg = dcfgOutDir dcfg </> tpkgName tpkg
 
-oneshotOutDir :: DirConfig -> TestPackage -> FilePath
-oneshotOutDir dcfg tpkg = dcfgOneShotOutDir dcfg </> tpkgName tpkg
-
-outFile :: DirConfig -> FilePath -> FilePath
-outFile dcfg file = dcfgOutDir dcfg </> file
+oneShotOutDir :: DirConfig -> TestPackage -> FilePath
+oneShotOutDir dcfg tpkg = dcfgOneShotOutDir dcfg </> tpkgName tpkg
 
-oneShotOutFile :: DirConfig -> FilePath -> FilePath
-oneShotOutFile dcfg file = dcfgOneShotOutDir dcfg </> file
+noCompilationOutDir :: DirConfig -> TestPackage -> FilePath
+noCompilationOutDir dcfg tpkg = dcfgNoCompilationOutDir dcfg </> tpkgName tpkg
 
 refFile :: DirConfig -> FilePath -> FilePath
 refFile dcfg file = dcfgRefDir dcfg </> file


=====================================
utils/haddock/haddock-test/src/Test/Haddock/Config.hs
=====================================
@@ -4,7 +4,7 @@
 module Test.Haddock.Config
     ( TestPackage(..), CheckConfig(..), DirConfig(..), Config(..)
     , defaultDirConfig
-    , cfgSrcDir, cfgRefDir, cfgOutDir, cfgResDir, cfgOneShotOutDir
+    , cfgSrcDir, cfgRefDir, cfgOutDir, cfgResDir, cfgOneShotOutDir, cfgNoCompilationOutDir
     , parseArgs, checkOpt, loadConfig
     ) where
 
@@ -58,9 +58,11 @@ data DirConfig = DirConfig
     , dcfgRefDir :: FilePath
     , dcfgOutDir :: FilePath
     , dcfgOneShotOutDir :: FilePath
+    , dcfgNoCompilationOutDir :: FilePath
     , dcfgResDir :: FilePath
     , dcfgCheckIgnore :: FilePath -> Bool
     , dcfgCheckIgnoreOneShot :: FilePath -> Bool
+    , dcfgCheckIgnoreNoCompilation :: FilePath -> Bool
     }
 
 
@@ -70,9 +72,11 @@ defaultDirConfig baseDir = DirConfig
     , dcfgRefDir = baseDir </> "ref"
     , dcfgOutDir = baseDir </> "out"
     , dcfgOneShotOutDir = baseDir </> "one-shot-out"
+    , dcfgNoCompilationOutDir = baseDir </> "no-compilation-out"
     , dcfgResDir = rootDir </> "resources"
     , dcfgCheckIgnore = const False
     , dcfgCheckIgnoreOneShot = const False
+    , dcfgCheckIgnoreNoCompilation = const False
     }
   where
     rootDir = baseDir </> ".."
@@ -92,12 +96,13 @@ data Config c = Config
     }
 
 
-cfgSrcDir, cfgRefDir, cfgOutDir, cfgResDir, cfgOneShotOutDir :: Config c -> FilePath
+cfgSrcDir, cfgRefDir, cfgOutDir, cfgResDir, cfgOneShotOutDir, cfgNoCompilationOutDir :: Config c -> FilePath
 cfgSrcDir = dcfgSrcDir . cfgDirConfig
 cfgRefDir = dcfgRefDir . cfgDirConfig
 cfgOutDir = dcfgOutDir . cfgDirConfig
 cfgResDir = dcfgResDir . cfgDirConfig
 cfgOneShotOutDir = dcfgOneShotOutDir . cfgDirConfig
+cfgNoCompilationOutDir = dcfgNoCompilationOutDir . cfgDirConfig
 
 
 


=====================================
utils/haddock/latex-test/Main.hs
=====================================
@@ -23,6 +23,7 @@ dirConfig = (defaultDirConfig $ takeDirectory __FILE__)
   { dcfgCheckIgnore = (`elem` ["haddock.sty", "main.tex"]) . takeFileName
   -- Just a discrepancy in output order
   , dcfgCheckIgnoreOneShot = (`elem` ["ConstructorArgs.tex"]) . takeFileName
+  , dcfgCheckIgnoreNoCompilation = (`elem` ["ConstructorArgs.tex"]) . takeFileName
   }
 
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1499764f729bfe8d36c317b5ee508e5d422fc494

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1499764f729bfe8d36c317b5ee508e5d422fc494
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240903/729b19e0/attachment-0001.html>


More information about the ghc-commits mailing list