[Git][ghc/ghc][wip/T25046_impl] 3 commits: haddock: decrease margin on top of small headings

Serge S. Gulin (@gulin.serge) gitlab at gitlab.haskell.org
Tue Aug 6 08:55:04 UTC 2024



Serge S. Gulin pushed to branch wip/T25046_impl at Glasgow Haskell Compiler / GHC


Commits:
af2ae742 by M. Taimoor Zaeem at 2024-08-03T18:52:50+05:00
haddock: decrease margin on top of small headings

- - - - -
a1e42e7a by Rodrigo Mesquita at 2024-08-05T21:03:04-04:00
hi: Deterministic ImportedMods in Usages

The `mi_usages` field of the interface files must use a deterministic
list of `Usage`s to guarantee a deterministic interface. However, this
list was, in its origins, constructed from a `ModuleEnv` which uses a
non-deterministic ordering that was leaking into the interface.

Specifically, ImportedMods = ModuleEnv ... would get converted to a list and
then passed to `mkUsageInfo` to construct the Usages.

The solution is simple. Back `ImportedMods` with a deterministic map.
`Map Module ...` is enough, since the Ord instance for `Module` already
uses a stable, deterministic, comparison.

Fixes #25131

- - - - -
eb1cb536 by Serge S. Gulin at 2024-08-06T08:54:55+00:00
testsuite: extend size performance tests with gzip (fixes #25046)

The main purpose is to create tests for minimal app (hello world and its variations, i.e. unicode used) distribution size metric.

Many platforms support distribution in compressed form via gzip. It would be nice to collect information on how much size is taken by the executional bundle for each platform at minimal edge case.

2 groups of tests are added:
1. We extend javascript backend size tests with gzip-enabled versions for all cases where an optimizing compiler is used (for now it is google closure compiler).
2. We add trivial hello world tests with gzip-enabled versions for all other platforms at CI pipeline where no external optimizing compiler is used.

- - - - -


19 changed files:

- compiler/GHC/Driver/Main.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Usage.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Unit/Module/Imported.hs
- compiler/GHC/Unit/Module/ModIface.hs
- testsuite/driver/testlib.py
- + testsuite/tests/perf/size/Makefile
- testsuite/tests/perf/size/all.T
- testsuite/tests/perf/size/javascript/Makefile
- − testsuite/tests/perf/size/javascript/T24602_perf_size.hs
- testsuite/tests/perf/size/javascript/all.T
- utils/haddock/CHANGES.md
- utils/haddock/haddock-api/resources/html/Linuwial.std-theme/linuwial.css


Changes:

=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -1489,7 +1489,7 @@ checkSafeImports tcg_env
   where
     impInfo  = tcg_imports tcg_env     -- ImportAvails
     imports  = imp_mods impInfo        -- ImportedMods
-    imports1 = moduleEnvToList imports -- (Module, [ImportedBy])
+    imports1 = M.toList imports -- (Module, [ImportedBy])
     imports' = map (fmap importedByUser) imports1 -- (Module, [ImportedModsVal])
     pkgReqs  = imp_trust_pkgs impInfo  -- [Unit]
 


=====================================
compiler/GHC/HsToCore/Docs.hs
=====================================
@@ -34,7 +34,6 @@ import GHC.IORef (readIORef)
 import GHC.Unit.Types
 import GHC.Hs
 import GHC.Types.Avail
-import GHC.Unit.Module
 import qualified Data.List.NonEmpty as NonEmpty
 import Data.List.NonEmpty (NonEmpty ((:|)))
 import GHC.Unit.Module.Imported
@@ -183,13 +182,12 @@ mkDocStructureFromExportList mdl import_avails export_list =
     aliasMap =
         M.fromListWith (<>) $
           (this_mdl_name, this_mdl_name :| [])
-          : (flip concatMap (moduleEnvToList imported) $ \(mdl, imvs) ->
+          : (flip concatMap (M.toList imported) $ \(mdl, imvs) ->
               [(imv_name imv, moduleName mdl :| []) | imv <- imvs])
       where
         this_mdl_name = moduleName mdl
 
-    imported :: ModuleEnv [ImportedModsVal]
-    imported = mapModuleEnv importedByUser (imp_mods import_avails)
+    imported = M.map importedByUser (imp_mods import_avails)
 
 -- | Figure out the documentation structure by correlating
 -- the module exports with the located declarations.


=====================================
compiler/GHC/HsToCore/Usage.hs
=====================================
@@ -208,7 +208,7 @@ mk_mod_usage_info uc home_unit home_unit_ids this_mod direct_imports used_names
     safe_implicit_imps_req = uc_safe_implicit_imps_req uc
 
     used_mods    = moduleEnvKeys ent_map
-    dir_imp_mods = moduleEnvKeys direct_imports
+    dir_imp_mods = Map.keys direct_imports
     all_mods     = used_mods ++ filter (`notElem` used_mods) dir_imp_mods
     usage_mods   = sortBy stableModuleCmp all_mods
                         -- canonical order is imported, to avoid interface-file
@@ -289,7 +289,7 @@ mk_mod_usage_info uc home_unit home_unit_ids this_mod direct_imports used_names
         by_is_safe (ImportedByUser imv) = imv_is_safe imv
         by_is_safe _ = False
         (is_direct_import, imp_safe)
-            = case lookupModuleEnv direct_imports mod of
+            = case Map.lookup mod direct_imports of
                 -- ezyang: I'm not sure if any is the correct
                 -- metric here. If safety was guaranteed to be uniform
                 -- across all imports, why did the old code only look


=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -573,7 +573,7 @@ calculateAvails home_unit other_home_units iface mod_safe' want_boot imported_by
 
 
   in ImportAvails {
-          imp_mods       = unitModuleEnv (mi_module iface) [imported_by],
+          imp_mods       = Map.singleton (mi_module iface) [imported_by],
           imp_orphs      = orphans,
           imp_finsts     = finsts,
           imp_sig_mods   = sig_mods,


=====================================
compiler/GHC/Rename/Unbound.hs
=====================================
@@ -66,6 +66,7 @@ import Data.List (sortBy, partition, nub)
 import Data.List.NonEmpty ( pattern (:|), NonEmpty )
 import Data.Function ( on )
 import qualified Data.Semigroup as S
+import qualified Data.Map as M
 
 {-
 ************************************************************************
@@ -339,7 +340,7 @@ importSuggestions looking_for global_env hpt currMod imports rdr_name
   -- What import statements provide "Mod" at all
   -- or, if this is an unqualified name, are not qualified imports
   interesting_imports = [ (mod, imp)
-    | (mod, mod_imports) <- moduleEnvToList (imp_mods imports)
+    | (mod, mod_imports) <- M.toList (imp_mods imports)
     , Just imp <- return $ pick (importedByUser mod_imports)
     ]
 


=====================================
compiler/GHC/Tc/Gen/Export.hs
=====================================
@@ -52,6 +52,7 @@ import Control.Monad ( when )
 import qualified Data.List.NonEmpty as NE
 import Data.Traversable   ( for )
 import Data.List ( sortBy )
+import qualified Data.Map as Map
 
 {-
 ************************************************************************
@@ -307,7 +308,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
       = [gre]
 
     imported_modules = [ imv_name imv
-                       | xs <- moduleEnvElts $ imp_mods imports
+                       | xs <- Map.elems $ imp_mods imports
                        , imv <- importedByUser xs ]
 
     exports_from_item :: ExportAccum -> LIE GhcPs


=====================================
compiler/GHC/Tc/Gen/Splice.hs
=====================================
@@ -2886,7 +2886,7 @@ reifyModule (TH.Module (TH.PkgName pkgString) (TH.ModName mString)) = do
   if (reifMod == this_mod) then reifyThisModule else reifyFromIface reifMod
     where
       reifyThisModule = do
-        usages <- fmap (map modToTHMod . moduleEnvKeys . imp_mods) getImports
+        usages <- fmap (map modToTHMod . Map.keys . imp_mods) getImports
         return $ TH.ModuleInfo usages
 
       reifyFromIface reifMod = do


=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -178,6 +178,7 @@ import Data.List.NonEmpty ( NonEmpty (..) )
 import qualified Data.List.NonEmpty as NE
 import Data.Ord
 import qualified Data.Set as S
+import qualified Data.Map as M
 import Data.Foldable ( for_ )
 import Data.Traversable ( for )
 
@@ -432,7 +433,7 @@ tcRnImports hsc_env import_decls
                 -- Check type-family consistency between imports.
                 -- See Note [The type family instance consistency story]
         ; traceRn "rn1: checking family instance consistency {" empty
-        ; let { dir_imp_mods = moduleEnvKeys
+        ; let { dir_imp_mods = M.keys
                              . imp_mods
                              $ imports }
         ; checkFamInstConsistency dir_imp_mods


=====================================
compiler/GHC/Tc/Types.hs
=====================================
@@ -176,6 +176,7 @@ import GHCi.RemoteTypes
 
 import Data.Set      ( Set )
 import qualified Data.Set as S
+import qualified Data.Map as M
 import Data.Dynamic  ( Dynamic )
 import Data.Map ( Map )
 import Data.Typeable ( TypeRep )
@@ -916,7 +917,7 @@ plusModDeps = plusInstalledModuleEnv plus_mod_dep
       -- perf/compiler/MultiLayerModules
 
 emptyImportAvails :: ImportAvails
-emptyImportAvails = ImportAvails { imp_mods          = emptyModuleEnv,
+emptyImportAvails = ImportAvails { imp_mods          = M.empty,
                                    imp_direct_dep_mods = emptyInstalledModuleEnv,
                                    imp_dep_direct_pkgs = S.empty,
                                    imp_sig_mods      = [],
@@ -947,7 +948,7 @@ plusImportAvails
                   imp_sig_mods = sig_mods2,
                   imp_trust_pkgs = tpkgs2, imp_trust_own_pkg = tself2,
                   imp_orphs = orphs2, imp_finsts = finsts2 })
-  = ImportAvails { imp_mods          = plusModuleEnv_C (++) mods1 mods2,
+  = ImportAvails { imp_mods          = M.unionWith (++) mods1 mods2,
                    imp_direct_dep_mods = ddmods1 `plusModDeps` ddmods2,
                    imp_dep_direct_pkgs      = ddpkgs1 `S.union` ddpkgs2,
                    imp_trust_pkgs    = tpkgs1 `S.union` tpkgs2,


=====================================
compiler/GHC/Unit/Module/Imported.hs
=====================================
@@ -13,10 +13,13 @@ import GHC.Unit.Module
 import GHC.Types.Name.Reader
 import GHC.Types.SafeHaskell
 import GHC.Types.SrcLoc
+import Data.Map (Map)
 
 -- | Records the modules directly imported by a module for extracting e.g.
 -- usage information, and also to give better error message
-type ImportedMods = ModuleEnv [ImportedBy]
+type ImportedMods = Map Module [ImportedBy]
+  -- We don't want to use a `ModuleEnv` since it would leak a non-deterministic
+  -- order to the interface files when passed as a list to `mkUsageInfo`.
 
 -- | If a module was "imported" by the user, we associate it with
 -- more detailed usage information 'ImportedModsVal'; a module


=====================================
compiler/GHC/Unit/Module/ModIface.hs
=====================================
@@ -245,6 +245,9 @@ data ModIface_ (phase :: ModIfacePhase)
                 -- doesn't affect the hash of this module)
                 -- NOT STRICT!  we read this field lazily from the interface file
                 -- It is *only* consulted by the recompilation checker
+                --
+                -- The elements must be *deterministically* sorted to guarantee
+                -- deterministic interface files
 
         mi_exports_  :: ![IfaceExport],
                 -- ^ Exports


=====================================
testsuite/driver/testlib.py
=====================================
@@ -1426,9 +1426,24 @@ async def test_common_work(name: TestName, opts,
             if needsTargetWrapper():
                 opts.skip = True
         elif func in [makefile_test, run_command]:
-            # makefile tests aren't necessarily runtime or compile-time
+            # Note [Makefile tests are supposed to be run in all ways]
+            # ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+            # Makefile tests aren't necessarily runtime or compile-time
             # specific. Assume we can run them in all ways. See #16042 for what
             # happened previously.
+            #
+            # For example, the WASM test environment requires a target wrapper to run tests
+            # which is why Makefile tests are skipped by default. For cases where the
+            # target wrapper is actually not needed we can trigger Makefile tests to run
+            # by using something like `pre_cmd('$MAKE -s --no-print-directory...`.
+            # Examples of this can be found throughout the code.
+            #
+            # Additionally, it is useful to set `multimod_compile` as the running mode
+            # because it provides enough flexibility to specify source names to compile
+            # without wasting time on running.
+            #
+            # `ignore_stdout` and `ignore_stderr` could also be helpful in cases where
+            # all you need is to compare the exit code with 0.
             all_ways = config.compile_ways + config.run_ways
             if needsTargetWrapper():
                 opts.skip = True


=====================================
testsuite/tests/perf/size/Makefile
=====================================
@@ -0,0 +1,11 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+size_hello_artifact_gzip:
+	'$(TEST_HC)' $(TEST_HC_OPTS) ./size_hello_artifact.hs -v0 -fforce-recomp
+	gzip --best "./size_hello_artifact$(exe_extension_from_python)"
+
+size_hello_unicode_gzip:
+	'$(TEST_HC)' $(TEST_HC_OPTS) ./size_hello_unicode.hs -v0 -fforce-recomp
+	gzip --best "./size_hello_unicode$(exe_extension_from_python)"


=====================================
testsuite/tests/perf/size/all.T
=====================================
@@ -3,8 +3,20 @@ test('size_hello_obj', [collect_size(5, 'size_hello_obj.o')], compile, [''])
 test('size_hello_artifact', [collect_size(5, 'size_hello_artifact' + exe_extension())],
                              compile_artifact, [''])
 
+test('size_hello_artifact_gzip', [extra_files(['./size_hello_artifact.hs']),
+  collect_size(5, 'size_hello_artifact' + exe_extension() + '.gz'),
+  # See Note [Makefile tests are supposed to be run in all ways] in testsuite/driver/testlib.py
+  pre_cmd('$MAKE -s --no-print-directory size_hello_artifact_gzip' + ' exe_extension_from_python="' + exe_extension() + '"'), ignore_stdout, ignore_stderr],
+  multimod_compile, ['size_hello_artifact', ''])
+
 test('size_hello_unicode', [collect_size(5, 'size_hello_unicode' + exe_extension())], compile_artifact, [''])
 
+test('size_hello_unicode_gzip', [extra_files(['./size_hello_unicode.hs']),
+  collect_size(5, 'size_hello_unicode' + exe_extension() + '.gz'),
+  # See Note [Makefile tests are supposed to be run in all ways] in testsuite/driver/testlib.py
+  pre_cmd('$MAKE -s --no-print-directory size_hello_unicode_gzip' + ' exe_extension_from_python="' + exe_extension() + '"'), ignore_stdout, ignore_stderr],
+  multimod_compile, ['size_hello_unicode', ''])
+
 size_acceptance_threshold = 100
 
 test('array_dir'           ,[collect_size_ghc_pkg(size_acceptance_threshold , 'array')]           , static_stats , [] )


=====================================
testsuite/tests/perf/size/javascript/Makefile
=====================================
@@ -3,7 +3,7 @@ include $(TOP)/mk/boilerplate.mk
 include $(TOP)/mk/test.mk
 
 T24602_perf_size:
-	'$(TEST_HC)' $(TEST_HC_OPTS) ./T24602_perf_size.hs -v0 -fforce-recomp
+	'$(TEST_HC)' $(TEST_HC_OPTS) ./size_hello_artifact.hs -v0 -fforce-recomp
 	google-closure-compiler \
 		--platform java \
 		--warning_level QUIET \
@@ -11,5 +11,23 @@ T24602_perf_size:
 		--assume_function_wrapper \
 		--compilation_level ADVANCED_OPTIMIZATIONS \
 		--emit_use_strict \
-		--js_output_file ./T24602_perf_size.jsexe/all.min.js \
-		./T24602_perf_size.jsexe/all.js ./T24602_perf_size.jsexe/all.externs.js
+		--js_output_file ./size_hello_artifact.jsexe/all.min.js \
+		./size_hello_artifact.jsexe/all.js ./size_hello_artifact.jsexe/all.externs.js
+
+T25046_perf_size_gzip: T24602_perf_size
+	gzip --best ./size_hello_artifact.jsexe/all.min.js
+
+T25046_perf_size_unicode:
+	'$(TEST_HC)' $(TEST_HC_OPTS) ./size_hello_unicode.hs -v0 -fforce-recomp
+	google-closure-compiler \
+		--platform java \
+		--warning_level QUIET \
+		--isolation_mode IIFE \
+		--assume_function_wrapper \
+		--compilation_level ADVANCED_OPTIMIZATIONS \
+		--emit_use_strict \
+		--js_output_file ./size_hello_unicode.jsexe/all.min.js \
+		./size_hello_unicode.jsexe/all.js ./size_hello_unicode.jsexe/all.externs.js
+
+T25046_perf_size_unicode_gzip: T25046_perf_size_unicode
+	gzip --best ./size_hello_unicode.jsexe/all.min.js


=====================================
testsuite/tests/perf/size/javascript/T24602_perf_size.hs deleted
=====================================
@@ -1,3 +0,0 @@
-module Main where
-
-main = print "Hello, JavaScript!"


=====================================
testsuite/tests/perf/size/javascript/all.T
=====================================
@@ -1,4 +1,7 @@
 # These are JavaScript-specific tests based on Google Closure Compiler
 setTestOpts(when(not(js_arch()),skip))
 
-test('T24602_perf_size', [collect_size(5, './T24602_perf_size.jsexe/all.min.js')], makefile_test, ['T24602_perf_size'])
+test('T24602_perf_size', [extra_files(['../size_hello_artifact.hs']), collect_size(5, './size_hello_artifact.jsexe/all.min.js')], makefile_test, ['T24602_perf_size'])
+test('T25046_perf_size_gzip', [extra_files(['../size_hello_artifact.hs']), collect_size(5, './size_hello_artifact.jsexe/all.min.js.gz')], makefile_test, ['T25046_perf_size_gzip'])
+test('T25046_perf_size_unicode', [extra_files(['../size_hello_unicode.hs']), collect_size(5, './size_hello_unicode.jsexe/all.min.js')], makefile_test, ['T25046_perf_size_unicode'])
+test('T25046_perf_size_unicode_gzip', [extra_files(['../size_hello_unicode.hs']), collect_size(5, './size_hello_unicode.jsexe/all.min.js.gz')], makefile_test, ['T25046_perf_size_unicode_gzip'])


=====================================
utils/haddock/CHANGES.md
=====================================
@@ -3,6 +3,8 @@
 
  * Add incremental mode to support rendering documentation one module at a time.
 
+ * Fix large margin on top of small headings
+
 ## Changes in 2.28.0
  * `hi-haddock` is integrated, which means docstrings are no longer extracted
    through typchecked module results. Instead, docstrings are taken from Haskell


=====================================
utils/haddock/haddock-api/resources/html/Linuwial.std-theme/linuwial.css
=====================================
@@ -295,10 +295,14 @@ pre, code, kbd, samp, tt, .src {
 }
 
 
-* + h1, * + h2, * + h3, * + h4, * + h5, * + h6 {
+* + h1, * + h2, * + h3 {
   margin-top: 2em;
 }
 
+* + h4 , * + h5, * + h6 {
+  margin-top: 1em;
+}
+
 h1 + h2, h2 + h3, h3 + h4, h4 + h5, h5 + h6 {
   margin-top: inherit;
 }



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bf3ef4f4afd5157a6b3bce9771713b9f9a08b9b5...eb1cb53647ff8770a29510a198b829a2426a5108

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bf3ef4f4afd5157a6b3bce9771713b9f9a08b9b5...eb1cb53647ff8770a29510a198b829a2426a5108
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/20240806/0d7dd569/attachment-0001.html>


More information about the ghc-commits mailing list